module Hydra.Langs.Haskell.Ast where
import qualified Hydra.Core as Core
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
data Alternative =
Alternative {
Alternative -> Pattern
alternativePattern :: Pattern,
Alternative -> CaseRhs
alternativeRhs :: CaseRhs,
Alternative -> Maybe LocalBindings
alternativeBinds :: (Maybe LocalBindings)}
deriving (Alternative -> Alternative -> Bool
(Alternative -> Alternative -> Bool)
-> (Alternative -> Alternative -> Bool) -> Eq Alternative
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Alternative -> Alternative -> Bool
== :: Alternative -> Alternative -> Bool
$c/= :: Alternative -> Alternative -> Bool
/= :: Alternative -> Alternative -> Bool
Eq, Eq Alternative
Eq Alternative =>
(Alternative -> Alternative -> Ordering)
-> (Alternative -> Alternative -> Bool)
-> (Alternative -> Alternative -> Bool)
-> (Alternative -> Alternative -> Bool)
-> (Alternative -> Alternative -> Bool)
-> (Alternative -> Alternative -> Alternative)
-> (Alternative -> Alternative -> Alternative)
-> Ord Alternative
Alternative -> Alternative -> Bool
Alternative -> Alternative -> Ordering
Alternative -> Alternative -> Alternative
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Alternative -> Alternative -> Ordering
compare :: Alternative -> Alternative -> Ordering
$c< :: Alternative -> Alternative -> Bool
< :: Alternative -> Alternative -> Bool
$c<= :: Alternative -> Alternative -> Bool
<= :: Alternative -> Alternative -> Bool
$c> :: Alternative -> Alternative -> Bool
> :: Alternative -> Alternative -> Bool
$c>= :: Alternative -> Alternative -> Bool
>= :: Alternative -> Alternative -> Bool
$cmax :: Alternative -> Alternative -> Alternative
max :: Alternative -> Alternative -> Alternative
$cmin :: Alternative -> Alternative -> Alternative
min :: Alternative -> Alternative -> Alternative
Ord, ReadPrec [Alternative]
ReadPrec Alternative
Int -> ReadS Alternative
ReadS [Alternative]
(Int -> ReadS Alternative)
-> ReadS [Alternative]
-> ReadPrec Alternative
-> ReadPrec [Alternative]
-> Read Alternative
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Alternative
readsPrec :: Int -> ReadS Alternative
$creadList :: ReadS [Alternative]
readList :: ReadS [Alternative]
$creadPrec :: ReadPrec Alternative
readPrec :: ReadPrec Alternative
$creadListPrec :: ReadPrec [Alternative]
readListPrec :: ReadPrec [Alternative]
Read, Int -> Alternative -> ShowS
[Alternative] -> ShowS
Alternative -> String
(Int -> Alternative -> ShowS)
-> (Alternative -> String)
-> ([Alternative] -> ShowS)
-> Show Alternative
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Alternative -> ShowS
showsPrec :: Int -> Alternative -> ShowS
$cshow :: Alternative -> String
show :: Alternative -> String
$cshowList :: [Alternative] -> ShowS
showList :: [Alternative] -> ShowS
Show)
_Alternative :: Name
_Alternative = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Alternative")
_Alternative_pattern :: Name
_Alternative_pattern = (String -> Name
Core.Name String
"pattern")
_Alternative_rhs :: Name
_Alternative_rhs = (String -> Name
Core.Name String
"rhs")
_Alternative_binds :: Name
_Alternative_binds = (String -> Name
Core.Name String
"binds")
data Assertion =
AssertionClass Assertion_Class |
AssertionTuple [Assertion]
deriving (Assertion -> Assertion -> Bool
(Assertion -> Assertion -> Bool)
-> (Assertion -> Assertion -> Bool) -> Eq Assertion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Assertion -> Assertion -> Bool
== :: Assertion -> Assertion -> Bool
$c/= :: Assertion -> Assertion -> Bool
/= :: Assertion -> Assertion -> Bool
Eq, Eq Assertion
Eq Assertion =>
(Assertion -> Assertion -> Ordering)
-> (Assertion -> Assertion -> Bool)
-> (Assertion -> Assertion -> Bool)
-> (Assertion -> Assertion -> Bool)
-> (Assertion -> Assertion -> Bool)
-> (Assertion -> Assertion -> Assertion)
-> (Assertion -> Assertion -> Assertion)
-> Ord Assertion
Assertion -> Assertion -> Bool
Assertion -> Assertion -> Ordering
Assertion -> Assertion -> Assertion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Assertion -> Assertion -> Ordering
compare :: Assertion -> Assertion -> Ordering
$c< :: Assertion -> Assertion -> Bool
< :: Assertion -> Assertion -> Bool
$c<= :: Assertion -> Assertion -> Bool
<= :: Assertion -> Assertion -> Bool
$c> :: Assertion -> Assertion -> Bool
> :: Assertion -> Assertion -> Bool
$c>= :: Assertion -> Assertion -> Bool
>= :: Assertion -> Assertion -> Bool
$cmax :: Assertion -> Assertion -> Assertion
max :: Assertion -> Assertion -> Assertion
$cmin :: Assertion -> Assertion -> Assertion
min :: Assertion -> Assertion -> Assertion
Ord, ReadPrec [Assertion]
ReadPrec Assertion
Int -> ReadS Assertion
ReadS [Assertion]
(Int -> ReadS Assertion)
-> ReadS [Assertion]
-> ReadPrec Assertion
-> ReadPrec [Assertion]
-> Read Assertion
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Assertion
readsPrec :: Int -> ReadS Assertion
$creadList :: ReadS [Assertion]
readList :: ReadS [Assertion]
$creadPrec :: ReadPrec Assertion
readPrec :: ReadPrec Assertion
$creadListPrec :: ReadPrec [Assertion]
readListPrec :: ReadPrec [Assertion]
Read, Int -> Assertion -> ShowS
[Assertion] -> ShowS
Assertion -> String
(Int -> Assertion -> ShowS)
-> (Assertion -> String)
-> ([Assertion] -> ShowS)
-> Show Assertion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Assertion -> ShowS
showsPrec :: Int -> Assertion -> ShowS
$cshow :: Assertion -> String
show :: Assertion -> String
$cshowList :: [Assertion] -> ShowS
showList :: [Assertion] -> ShowS
Show)
_Assertion :: Name
_Assertion = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Assertion")
_Assertion_class :: Name
_Assertion_class = (String -> Name
Core.Name String
"class")
_Assertion_tuple :: Name
_Assertion_tuple = (String -> Name
Core.Name String
"tuple")
data Assertion_Class =
Assertion_Class {
Assertion_Class -> Name
assertion_ClassName :: Name,
Assertion_Class -> [Type]
assertion_ClassTypes :: [Type]}
deriving (Assertion_Class -> Assertion_Class -> Bool
(Assertion_Class -> Assertion_Class -> Bool)
-> (Assertion_Class -> Assertion_Class -> Bool)
-> Eq Assertion_Class
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Assertion_Class -> Assertion_Class -> Bool
== :: Assertion_Class -> Assertion_Class -> Bool
$c/= :: Assertion_Class -> Assertion_Class -> Bool
/= :: Assertion_Class -> Assertion_Class -> Bool
Eq, Eq Assertion_Class
Eq Assertion_Class =>
(Assertion_Class -> Assertion_Class -> Ordering)
-> (Assertion_Class -> Assertion_Class -> Bool)
-> (Assertion_Class -> Assertion_Class -> Bool)
-> (Assertion_Class -> Assertion_Class -> Bool)
-> (Assertion_Class -> Assertion_Class -> Bool)
-> (Assertion_Class -> Assertion_Class -> Assertion_Class)
-> (Assertion_Class -> Assertion_Class -> Assertion_Class)
-> Ord Assertion_Class
Assertion_Class -> Assertion_Class -> Bool
Assertion_Class -> Assertion_Class -> Ordering
Assertion_Class -> Assertion_Class -> Assertion_Class
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Assertion_Class -> Assertion_Class -> Ordering
compare :: Assertion_Class -> Assertion_Class -> Ordering
$c< :: Assertion_Class -> Assertion_Class -> Bool
< :: Assertion_Class -> Assertion_Class -> Bool
$c<= :: Assertion_Class -> Assertion_Class -> Bool
<= :: Assertion_Class -> Assertion_Class -> Bool
$c> :: Assertion_Class -> Assertion_Class -> Bool
> :: Assertion_Class -> Assertion_Class -> Bool
$c>= :: Assertion_Class -> Assertion_Class -> Bool
>= :: Assertion_Class -> Assertion_Class -> Bool
$cmax :: Assertion_Class -> Assertion_Class -> Assertion_Class
max :: Assertion_Class -> Assertion_Class -> Assertion_Class
$cmin :: Assertion_Class -> Assertion_Class -> Assertion_Class
min :: Assertion_Class -> Assertion_Class -> Assertion_Class
Ord, ReadPrec [Assertion_Class]
ReadPrec Assertion_Class
Int -> ReadS Assertion_Class
ReadS [Assertion_Class]
(Int -> ReadS Assertion_Class)
-> ReadS [Assertion_Class]
-> ReadPrec Assertion_Class
-> ReadPrec [Assertion_Class]
-> Read Assertion_Class
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Assertion_Class
readsPrec :: Int -> ReadS Assertion_Class
$creadList :: ReadS [Assertion_Class]
readList :: ReadS [Assertion_Class]
$creadPrec :: ReadPrec Assertion_Class
readPrec :: ReadPrec Assertion_Class
$creadListPrec :: ReadPrec [Assertion_Class]
readListPrec :: ReadPrec [Assertion_Class]
Read, Int -> Assertion_Class -> ShowS
[Assertion_Class] -> ShowS
Assertion_Class -> String
(Int -> Assertion_Class -> ShowS)
-> (Assertion_Class -> String)
-> ([Assertion_Class] -> ShowS)
-> Show Assertion_Class
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Assertion_Class -> ShowS
showsPrec :: Int -> Assertion_Class -> ShowS
$cshow :: Assertion_Class -> String
show :: Assertion_Class -> String
$cshowList :: [Assertion_Class] -> ShowS
showList :: [Assertion_Class] -> ShowS
Show)
_Assertion_Class :: Name
_Assertion_Class = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Assertion.Class")
_Assertion_Class_name :: Name
_Assertion_Class_name = (String -> Name
Core.Name String
"name")
_Assertion_Class_types :: Name
_Assertion_Class_types = (String -> Name
Core.Name String
"types")
newtype CaseRhs =
CaseRhs {
CaseRhs -> Expression
unCaseRhs :: Expression}
deriving (CaseRhs -> CaseRhs -> Bool
(CaseRhs -> CaseRhs -> Bool)
-> (CaseRhs -> CaseRhs -> Bool) -> Eq CaseRhs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CaseRhs -> CaseRhs -> Bool
== :: CaseRhs -> CaseRhs -> Bool
$c/= :: CaseRhs -> CaseRhs -> Bool
/= :: CaseRhs -> CaseRhs -> Bool
Eq, Eq CaseRhs
Eq CaseRhs =>
(CaseRhs -> CaseRhs -> Ordering)
-> (CaseRhs -> CaseRhs -> Bool)
-> (CaseRhs -> CaseRhs -> Bool)
-> (CaseRhs -> CaseRhs -> Bool)
-> (CaseRhs -> CaseRhs -> Bool)
-> (CaseRhs -> CaseRhs -> CaseRhs)
-> (CaseRhs -> CaseRhs -> CaseRhs)
-> Ord CaseRhs
CaseRhs -> CaseRhs -> Bool
CaseRhs -> CaseRhs -> Ordering
CaseRhs -> CaseRhs -> CaseRhs
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CaseRhs -> CaseRhs -> Ordering
compare :: CaseRhs -> CaseRhs -> Ordering
$c< :: CaseRhs -> CaseRhs -> Bool
< :: CaseRhs -> CaseRhs -> Bool
$c<= :: CaseRhs -> CaseRhs -> Bool
<= :: CaseRhs -> CaseRhs -> Bool
$c> :: CaseRhs -> CaseRhs -> Bool
> :: CaseRhs -> CaseRhs -> Bool
$c>= :: CaseRhs -> CaseRhs -> Bool
>= :: CaseRhs -> CaseRhs -> Bool
$cmax :: CaseRhs -> CaseRhs -> CaseRhs
max :: CaseRhs -> CaseRhs -> CaseRhs
$cmin :: CaseRhs -> CaseRhs -> CaseRhs
min :: CaseRhs -> CaseRhs -> CaseRhs
Ord, ReadPrec [CaseRhs]
ReadPrec CaseRhs
Int -> ReadS CaseRhs
ReadS [CaseRhs]
(Int -> ReadS CaseRhs)
-> ReadS [CaseRhs]
-> ReadPrec CaseRhs
-> ReadPrec [CaseRhs]
-> Read CaseRhs
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CaseRhs
readsPrec :: Int -> ReadS CaseRhs
$creadList :: ReadS [CaseRhs]
readList :: ReadS [CaseRhs]
$creadPrec :: ReadPrec CaseRhs
readPrec :: ReadPrec CaseRhs
$creadListPrec :: ReadPrec [CaseRhs]
readListPrec :: ReadPrec [CaseRhs]
Read, Int -> CaseRhs -> ShowS
[CaseRhs] -> ShowS
CaseRhs -> String
(Int -> CaseRhs -> ShowS)
-> (CaseRhs -> String) -> ([CaseRhs] -> ShowS) -> Show CaseRhs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CaseRhs -> ShowS
showsPrec :: Int -> CaseRhs -> ShowS
$cshow :: CaseRhs -> String
show :: CaseRhs -> String
$cshowList :: [CaseRhs] -> ShowS
showList :: [CaseRhs] -> ShowS
Show)
_CaseRhs :: Name
_CaseRhs = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.CaseRhs")
data Constructor =
ConstructorOrdinary Constructor_Ordinary |
ConstructorRecord Constructor_Record
deriving (Constructor -> Constructor -> Bool
(Constructor -> Constructor -> Bool)
-> (Constructor -> Constructor -> Bool) -> Eq Constructor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Constructor -> Constructor -> Bool
== :: Constructor -> Constructor -> Bool
$c/= :: Constructor -> Constructor -> Bool
/= :: Constructor -> Constructor -> Bool
Eq, Eq Constructor
Eq Constructor =>
(Constructor -> Constructor -> Ordering)
-> (Constructor -> Constructor -> Bool)
-> (Constructor -> Constructor -> Bool)
-> (Constructor -> Constructor -> Bool)
-> (Constructor -> Constructor -> Bool)
-> (Constructor -> Constructor -> Constructor)
-> (Constructor -> Constructor -> Constructor)
-> Ord Constructor
Constructor -> Constructor -> Bool
Constructor -> Constructor -> Ordering
Constructor -> Constructor -> Constructor
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Constructor -> Constructor -> Ordering
compare :: Constructor -> Constructor -> Ordering
$c< :: Constructor -> Constructor -> Bool
< :: Constructor -> Constructor -> Bool
$c<= :: Constructor -> Constructor -> Bool
<= :: Constructor -> Constructor -> Bool
$c> :: Constructor -> Constructor -> Bool
> :: Constructor -> Constructor -> Bool
$c>= :: Constructor -> Constructor -> Bool
>= :: Constructor -> Constructor -> Bool
$cmax :: Constructor -> Constructor -> Constructor
max :: Constructor -> Constructor -> Constructor
$cmin :: Constructor -> Constructor -> Constructor
min :: Constructor -> Constructor -> Constructor
Ord, ReadPrec [Constructor]
ReadPrec Constructor
Int -> ReadS Constructor
ReadS [Constructor]
(Int -> ReadS Constructor)
-> ReadS [Constructor]
-> ReadPrec Constructor
-> ReadPrec [Constructor]
-> Read Constructor
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Constructor
readsPrec :: Int -> ReadS Constructor
$creadList :: ReadS [Constructor]
readList :: ReadS [Constructor]
$creadPrec :: ReadPrec Constructor
readPrec :: ReadPrec Constructor
$creadListPrec :: ReadPrec [Constructor]
readListPrec :: ReadPrec [Constructor]
Read, Int -> Constructor -> ShowS
[Constructor] -> ShowS
Constructor -> String
(Int -> Constructor -> ShowS)
-> (Constructor -> String)
-> ([Constructor] -> ShowS)
-> Show Constructor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Constructor -> ShowS
showsPrec :: Int -> Constructor -> ShowS
$cshow :: Constructor -> String
show :: Constructor -> String
$cshowList :: [Constructor] -> ShowS
showList :: [Constructor] -> ShowS
Show)
_Constructor :: Name
_Constructor = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Constructor")
_Constructor_ordinary :: Name
_Constructor_ordinary = (String -> Name
Core.Name String
"ordinary")
_Constructor_record :: Name
_Constructor_record = (String -> Name
Core.Name String
"record")
data Constructor_Ordinary =
Constructor_Ordinary {
Constructor_Ordinary -> Name
constructor_OrdinaryName :: Name,
Constructor_Ordinary -> [Type]
constructor_OrdinaryFields :: [Type]}
deriving (Constructor_Ordinary -> Constructor_Ordinary -> Bool
(Constructor_Ordinary -> Constructor_Ordinary -> Bool)
-> (Constructor_Ordinary -> Constructor_Ordinary -> Bool)
-> Eq Constructor_Ordinary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
== :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
$c/= :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
/= :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
Eq, Eq Constructor_Ordinary
Eq Constructor_Ordinary =>
(Constructor_Ordinary -> Constructor_Ordinary -> Ordering)
-> (Constructor_Ordinary -> Constructor_Ordinary -> Bool)
-> (Constructor_Ordinary -> Constructor_Ordinary -> Bool)
-> (Constructor_Ordinary -> Constructor_Ordinary -> Bool)
-> (Constructor_Ordinary -> Constructor_Ordinary -> Bool)
-> (Constructor_Ordinary
-> Constructor_Ordinary -> Constructor_Ordinary)
-> (Constructor_Ordinary
-> Constructor_Ordinary -> Constructor_Ordinary)
-> Ord Constructor_Ordinary
Constructor_Ordinary -> Constructor_Ordinary -> Bool
Constructor_Ordinary -> Constructor_Ordinary -> Ordering
Constructor_Ordinary
-> Constructor_Ordinary -> Constructor_Ordinary
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Constructor_Ordinary -> Constructor_Ordinary -> Ordering
compare :: Constructor_Ordinary -> Constructor_Ordinary -> Ordering
$c< :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
< :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
$c<= :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
<= :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
$c> :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
> :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
$c>= :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
>= :: Constructor_Ordinary -> Constructor_Ordinary -> Bool
$cmax :: Constructor_Ordinary
-> Constructor_Ordinary -> Constructor_Ordinary
max :: Constructor_Ordinary
-> Constructor_Ordinary -> Constructor_Ordinary
$cmin :: Constructor_Ordinary
-> Constructor_Ordinary -> Constructor_Ordinary
min :: Constructor_Ordinary
-> Constructor_Ordinary -> Constructor_Ordinary
Ord, ReadPrec [Constructor_Ordinary]
ReadPrec Constructor_Ordinary
Int -> ReadS Constructor_Ordinary
ReadS [Constructor_Ordinary]
(Int -> ReadS Constructor_Ordinary)
-> ReadS [Constructor_Ordinary]
-> ReadPrec Constructor_Ordinary
-> ReadPrec [Constructor_Ordinary]
-> Read Constructor_Ordinary
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Constructor_Ordinary
readsPrec :: Int -> ReadS Constructor_Ordinary
$creadList :: ReadS [Constructor_Ordinary]
readList :: ReadS [Constructor_Ordinary]
$creadPrec :: ReadPrec Constructor_Ordinary
readPrec :: ReadPrec Constructor_Ordinary
$creadListPrec :: ReadPrec [Constructor_Ordinary]
readListPrec :: ReadPrec [Constructor_Ordinary]
Read, Int -> Constructor_Ordinary -> ShowS
[Constructor_Ordinary] -> ShowS
Constructor_Ordinary -> String
(Int -> Constructor_Ordinary -> ShowS)
-> (Constructor_Ordinary -> String)
-> ([Constructor_Ordinary] -> ShowS)
-> Show Constructor_Ordinary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Constructor_Ordinary -> ShowS
showsPrec :: Int -> Constructor_Ordinary -> ShowS
$cshow :: Constructor_Ordinary -> String
show :: Constructor_Ordinary -> String
$cshowList :: [Constructor_Ordinary] -> ShowS
showList :: [Constructor_Ordinary] -> ShowS
Show)
_Constructor_Ordinary :: Name
_Constructor_Ordinary = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Constructor.Ordinary")
_Constructor_Ordinary_name :: Name
_Constructor_Ordinary_name = (String -> Name
Core.Name String
"name")
_Constructor_Ordinary_fields :: Name
_Constructor_Ordinary_fields = (String -> Name
Core.Name String
"fields")
data Constructor_Record =
Constructor_Record {
Constructor_Record -> Name
constructor_RecordName :: Name,
Constructor_Record -> [FieldWithComments]
constructor_RecordFields :: [FieldWithComments]}
deriving (Constructor_Record -> Constructor_Record -> Bool
(Constructor_Record -> Constructor_Record -> Bool)
-> (Constructor_Record -> Constructor_Record -> Bool)
-> Eq Constructor_Record
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Constructor_Record -> Constructor_Record -> Bool
== :: Constructor_Record -> Constructor_Record -> Bool
$c/= :: Constructor_Record -> Constructor_Record -> Bool
/= :: Constructor_Record -> Constructor_Record -> Bool
Eq, Eq Constructor_Record
Eq Constructor_Record =>
(Constructor_Record -> Constructor_Record -> Ordering)
-> (Constructor_Record -> Constructor_Record -> Bool)
-> (Constructor_Record -> Constructor_Record -> Bool)
-> (Constructor_Record -> Constructor_Record -> Bool)
-> (Constructor_Record -> Constructor_Record -> Bool)
-> (Constructor_Record -> Constructor_Record -> Constructor_Record)
-> (Constructor_Record -> Constructor_Record -> Constructor_Record)
-> Ord Constructor_Record
Constructor_Record -> Constructor_Record -> Bool
Constructor_Record -> Constructor_Record -> Ordering
Constructor_Record -> Constructor_Record -> Constructor_Record
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Constructor_Record -> Constructor_Record -> Ordering
compare :: Constructor_Record -> Constructor_Record -> Ordering
$c< :: Constructor_Record -> Constructor_Record -> Bool
< :: Constructor_Record -> Constructor_Record -> Bool
$c<= :: Constructor_Record -> Constructor_Record -> Bool
<= :: Constructor_Record -> Constructor_Record -> Bool
$c> :: Constructor_Record -> Constructor_Record -> Bool
> :: Constructor_Record -> Constructor_Record -> Bool
$c>= :: Constructor_Record -> Constructor_Record -> Bool
>= :: Constructor_Record -> Constructor_Record -> Bool
$cmax :: Constructor_Record -> Constructor_Record -> Constructor_Record
max :: Constructor_Record -> Constructor_Record -> Constructor_Record
$cmin :: Constructor_Record -> Constructor_Record -> Constructor_Record
min :: Constructor_Record -> Constructor_Record -> Constructor_Record
Ord, ReadPrec [Constructor_Record]
ReadPrec Constructor_Record
Int -> ReadS Constructor_Record
ReadS [Constructor_Record]
(Int -> ReadS Constructor_Record)
-> ReadS [Constructor_Record]
-> ReadPrec Constructor_Record
-> ReadPrec [Constructor_Record]
-> Read Constructor_Record
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Constructor_Record
readsPrec :: Int -> ReadS Constructor_Record
$creadList :: ReadS [Constructor_Record]
readList :: ReadS [Constructor_Record]
$creadPrec :: ReadPrec Constructor_Record
readPrec :: ReadPrec Constructor_Record
$creadListPrec :: ReadPrec [Constructor_Record]
readListPrec :: ReadPrec [Constructor_Record]
Read, Int -> Constructor_Record -> ShowS
[Constructor_Record] -> ShowS
Constructor_Record -> String
(Int -> Constructor_Record -> ShowS)
-> (Constructor_Record -> String)
-> ([Constructor_Record] -> ShowS)
-> Show Constructor_Record
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Constructor_Record -> ShowS
showsPrec :: Int -> Constructor_Record -> ShowS
$cshow :: Constructor_Record -> String
show :: Constructor_Record -> String
$cshowList :: [Constructor_Record] -> ShowS
showList :: [Constructor_Record] -> ShowS
Show)
_Constructor_Record :: Name
_Constructor_Record = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Constructor.Record")
_Constructor_Record_name :: Name
_Constructor_Record_name = (String -> Name
Core.Name String
"name")
_Constructor_Record_fields :: Name
_Constructor_Record_fields = (String -> Name
Core.Name String
"fields")
data =
{
ConstructorWithComments -> Constructor
constructorWithCommentsBody :: Constructor,
:: (Maybe String)}
deriving (ConstructorWithComments -> ConstructorWithComments -> Bool
(ConstructorWithComments -> ConstructorWithComments -> Bool)
-> (ConstructorWithComments -> ConstructorWithComments -> Bool)
-> Eq ConstructorWithComments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConstructorWithComments -> ConstructorWithComments -> Bool
== :: ConstructorWithComments -> ConstructorWithComments -> Bool
$c/= :: ConstructorWithComments -> ConstructorWithComments -> Bool
/= :: ConstructorWithComments -> ConstructorWithComments -> Bool
Eq, Eq ConstructorWithComments
Eq ConstructorWithComments =>
(ConstructorWithComments -> ConstructorWithComments -> Ordering)
-> (ConstructorWithComments -> ConstructorWithComments -> Bool)
-> (ConstructorWithComments -> ConstructorWithComments -> Bool)
-> (ConstructorWithComments -> ConstructorWithComments -> Bool)
-> (ConstructorWithComments -> ConstructorWithComments -> Bool)
-> (ConstructorWithComments
-> ConstructorWithComments -> ConstructorWithComments)
-> (ConstructorWithComments
-> ConstructorWithComments -> ConstructorWithComments)
-> Ord ConstructorWithComments
ConstructorWithComments -> ConstructorWithComments -> Bool
ConstructorWithComments -> ConstructorWithComments -> Ordering
ConstructorWithComments
-> ConstructorWithComments -> ConstructorWithComments
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ConstructorWithComments -> ConstructorWithComments -> Ordering
compare :: ConstructorWithComments -> ConstructorWithComments -> Ordering
$c< :: ConstructorWithComments -> ConstructorWithComments -> Bool
< :: ConstructorWithComments -> ConstructorWithComments -> Bool
$c<= :: ConstructorWithComments -> ConstructorWithComments -> Bool
<= :: ConstructorWithComments -> ConstructorWithComments -> Bool
$c> :: ConstructorWithComments -> ConstructorWithComments -> Bool
> :: ConstructorWithComments -> ConstructorWithComments -> Bool
$c>= :: ConstructorWithComments -> ConstructorWithComments -> Bool
>= :: ConstructorWithComments -> ConstructorWithComments -> Bool
$cmax :: ConstructorWithComments
-> ConstructorWithComments -> ConstructorWithComments
max :: ConstructorWithComments
-> ConstructorWithComments -> ConstructorWithComments
$cmin :: ConstructorWithComments
-> ConstructorWithComments -> ConstructorWithComments
min :: ConstructorWithComments
-> ConstructorWithComments -> ConstructorWithComments
Ord, ReadPrec [ConstructorWithComments]
ReadPrec ConstructorWithComments
Int -> ReadS ConstructorWithComments
ReadS [ConstructorWithComments]
(Int -> ReadS ConstructorWithComments)
-> ReadS [ConstructorWithComments]
-> ReadPrec ConstructorWithComments
-> ReadPrec [ConstructorWithComments]
-> Read ConstructorWithComments
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ConstructorWithComments
readsPrec :: Int -> ReadS ConstructorWithComments
$creadList :: ReadS [ConstructorWithComments]
readList :: ReadS [ConstructorWithComments]
$creadPrec :: ReadPrec ConstructorWithComments
readPrec :: ReadPrec ConstructorWithComments
$creadListPrec :: ReadPrec [ConstructorWithComments]
readListPrec :: ReadPrec [ConstructorWithComments]
Read, Int -> ConstructorWithComments -> ShowS
[ConstructorWithComments] -> ShowS
ConstructorWithComments -> String
(Int -> ConstructorWithComments -> ShowS)
-> (ConstructorWithComments -> String)
-> ([ConstructorWithComments] -> ShowS)
-> Show ConstructorWithComments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConstructorWithComments -> ShowS
showsPrec :: Int -> ConstructorWithComments -> ShowS
$cshow :: ConstructorWithComments -> String
show :: ConstructorWithComments -> String
$cshowList :: [ConstructorWithComments] -> ShowS
showList :: [ConstructorWithComments] -> ShowS
Show)
= (String -> Name
Core.Name String
"hydra/langs/haskell/ast.ConstructorWithComments")
_ConstructorWithComments_body :: Name
_ConstructorWithComments_body = (String -> Name
Core.Name String
"body")
= (String -> Name
Core.Name String
"comments")
data DataDeclaration =
DataDeclaration {
DataDeclaration -> DataDeclaration_Keyword
dataDeclarationKeyword :: DataDeclaration_Keyword,
DataDeclaration -> [Assertion]
dataDeclarationContext :: [Assertion],
DataDeclaration -> DeclarationHead
dataDeclarationHead :: DeclarationHead,
DataDeclaration -> [ConstructorWithComments]
dataDeclarationConstructors :: [ConstructorWithComments],
DataDeclaration -> [Deriving]
dataDeclarationDeriving :: [Deriving]}
deriving (DataDeclaration -> DataDeclaration -> Bool
(DataDeclaration -> DataDeclaration -> Bool)
-> (DataDeclaration -> DataDeclaration -> Bool)
-> Eq DataDeclaration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataDeclaration -> DataDeclaration -> Bool
== :: DataDeclaration -> DataDeclaration -> Bool
$c/= :: DataDeclaration -> DataDeclaration -> Bool
/= :: DataDeclaration -> DataDeclaration -> Bool
Eq, Eq DataDeclaration
Eq DataDeclaration =>
(DataDeclaration -> DataDeclaration -> Ordering)
-> (DataDeclaration -> DataDeclaration -> Bool)
-> (DataDeclaration -> DataDeclaration -> Bool)
-> (DataDeclaration -> DataDeclaration -> Bool)
-> (DataDeclaration -> DataDeclaration -> Bool)
-> (DataDeclaration -> DataDeclaration -> DataDeclaration)
-> (DataDeclaration -> DataDeclaration -> DataDeclaration)
-> Ord DataDeclaration
DataDeclaration -> DataDeclaration -> Bool
DataDeclaration -> DataDeclaration -> Ordering
DataDeclaration -> DataDeclaration -> DataDeclaration
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataDeclaration -> DataDeclaration -> Ordering
compare :: DataDeclaration -> DataDeclaration -> Ordering
$c< :: DataDeclaration -> DataDeclaration -> Bool
< :: DataDeclaration -> DataDeclaration -> Bool
$c<= :: DataDeclaration -> DataDeclaration -> Bool
<= :: DataDeclaration -> DataDeclaration -> Bool
$c> :: DataDeclaration -> DataDeclaration -> Bool
> :: DataDeclaration -> DataDeclaration -> Bool
$c>= :: DataDeclaration -> DataDeclaration -> Bool
>= :: DataDeclaration -> DataDeclaration -> Bool
$cmax :: DataDeclaration -> DataDeclaration -> DataDeclaration
max :: DataDeclaration -> DataDeclaration -> DataDeclaration
$cmin :: DataDeclaration -> DataDeclaration -> DataDeclaration
min :: DataDeclaration -> DataDeclaration -> DataDeclaration
Ord, ReadPrec [DataDeclaration]
ReadPrec DataDeclaration
Int -> ReadS DataDeclaration
ReadS [DataDeclaration]
(Int -> ReadS DataDeclaration)
-> ReadS [DataDeclaration]
-> ReadPrec DataDeclaration
-> ReadPrec [DataDeclaration]
-> Read DataDeclaration
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataDeclaration
readsPrec :: Int -> ReadS DataDeclaration
$creadList :: ReadS [DataDeclaration]
readList :: ReadS [DataDeclaration]
$creadPrec :: ReadPrec DataDeclaration
readPrec :: ReadPrec DataDeclaration
$creadListPrec :: ReadPrec [DataDeclaration]
readListPrec :: ReadPrec [DataDeclaration]
Read, Int -> DataDeclaration -> ShowS
[DataDeclaration] -> ShowS
DataDeclaration -> String
(Int -> DataDeclaration -> ShowS)
-> (DataDeclaration -> String)
-> ([DataDeclaration] -> ShowS)
-> Show DataDeclaration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataDeclaration -> ShowS
showsPrec :: Int -> DataDeclaration -> ShowS
$cshow :: DataDeclaration -> String
show :: DataDeclaration -> String
$cshowList :: [DataDeclaration] -> ShowS
showList :: [DataDeclaration] -> ShowS
Show)
_DataDeclaration :: Name
_DataDeclaration = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.DataDeclaration")
_DataDeclaration_keyword :: Name
_DataDeclaration_keyword = (String -> Name
Core.Name String
"keyword")
_DataDeclaration_context :: Name
_DataDeclaration_context = (String -> Name
Core.Name String
"context")
_DataDeclaration_head :: Name
_DataDeclaration_head = (String -> Name
Core.Name String
"head")
_DataDeclaration_constructors :: Name
_DataDeclaration_constructors = (String -> Name
Core.Name String
"constructors")
_DataDeclaration_deriving :: Name
_DataDeclaration_deriving = (String -> Name
Core.Name String
"deriving")
data DataDeclaration_Keyword =
DataDeclaration_KeywordData |
DataDeclaration_KeywordNewtype
deriving (DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
(DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool)
-> (DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool)
-> Eq DataDeclaration_Keyword
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
== :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
$c/= :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
/= :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
Eq, Eq DataDeclaration_Keyword
Eq DataDeclaration_Keyword =>
(DataDeclaration_Keyword -> DataDeclaration_Keyword -> Ordering)
-> (DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool)
-> (DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool)
-> (DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool)
-> (DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool)
-> (DataDeclaration_Keyword
-> DataDeclaration_Keyword -> DataDeclaration_Keyword)
-> (DataDeclaration_Keyword
-> DataDeclaration_Keyword -> DataDeclaration_Keyword)
-> Ord DataDeclaration_Keyword
DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
DataDeclaration_Keyword -> DataDeclaration_Keyword -> Ordering
DataDeclaration_Keyword
-> DataDeclaration_Keyword -> DataDeclaration_Keyword
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Ordering
compare :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Ordering
$c< :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
< :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
$c<= :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
<= :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
$c> :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
> :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
$c>= :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
>= :: DataDeclaration_Keyword -> DataDeclaration_Keyword -> Bool
$cmax :: DataDeclaration_Keyword
-> DataDeclaration_Keyword -> DataDeclaration_Keyword
max :: DataDeclaration_Keyword
-> DataDeclaration_Keyword -> DataDeclaration_Keyword
$cmin :: DataDeclaration_Keyword
-> DataDeclaration_Keyword -> DataDeclaration_Keyword
min :: DataDeclaration_Keyword
-> DataDeclaration_Keyword -> DataDeclaration_Keyword
Ord, ReadPrec [DataDeclaration_Keyword]
ReadPrec DataDeclaration_Keyword
Int -> ReadS DataDeclaration_Keyword
ReadS [DataDeclaration_Keyword]
(Int -> ReadS DataDeclaration_Keyword)
-> ReadS [DataDeclaration_Keyword]
-> ReadPrec DataDeclaration_Keyword
-> ReadPrec [DataDeclaration_Keyword]
-> Read DataDeclaration_Keyword
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataDeclaration_Keyword
readsPrec :: Int -> ReadS DataDeclaration_Keyword
$creadList :: ReadS [DataDeclaration_Keyword]
readList :: ReadS [DataDeclaration_Keyword]
$creadPrec :: ReadPrec DataDeclaration_Keyword
readPrec :: ReadPrec DataDeclaration_Keyword
$creadListPrec :: ReadPrec [DataDeclaration_Keyword]
readListPrec :: ReadPrec [DataDeclaration_Keyword]
Read, Int -> DataDeclaration_Keyword -> ShowS
[DataDeclaration_Keyword] -> ShowS
DataDeclaration_Keyword -> String
(Int -> DataDeclaration_Keyword -> ShowS)
-> (DataDeclaration_Keyword -> String)
-> ([DataDeclaration_Keyword] -> ShowS)
-> Show DataDeclaration_Keyword
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataDeclaration_Keyword -> ShowS
showsPrec :: Int -> DataDeclaration_Keyword -> ShowS
$cshow :: DataDeclaration_Keyword -> String
show :: DataDeclaration_Keyword -> String
$cshowList :: [DataDeclaration_Keyword] -> ShowS
showList :: [DataDeclaration_Keyword] -> ShowS
Show)
_DataDeclaration_Keyword :: Name
_DataDeclaration_Keyword = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.DataDeclaration.Keyword")
_DataDeclaration_Keyword_data :: Name
_DataDeclaration_Keyword_data = (String -> Name
Core.Name String
"data")
_DataDeclaration_Keyword_newtype :: Name
_DataDeclaration_Keyword_newtype = (String -> Name
Core.Name String
"newtype")
data =
{
DeclarationWithComments -> Declaration
declarationWithCommentsBody :: Declaration,
:: (Maybe String)}
deriving (DeclarationWithComments -> DeclarationWithComments -> Bool
(DeclarationWithComments -> DeclarationWithComments -> Bool)
-> (DeclarationWithComments -> DeclarationWithComments -> Bool)
-> Eq DeclarationWithComments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeclarationWithComments -> DeclarationWithComments -> Bool
== :: DeclarationWithComments -> DeclarationWithComments -> Bool
$c/= :: DeclarationWithComments -> DeclarationWithComments -> Bool
/= :: DeclarationWithComments -> DeclarationWithComments -> Bool
Eq, Eq DeclarationWithComments
Eq DeclarationWithComments =>
(DeclarationWithComments -> DeclarationWithComments -> Ordering)
-> (DeclarationWithComments -> DeclarationWithComments -> Bool)
-> (DeclarationWithComments -> DeclarationWithComments -> Bool)
-> (DeclarationWithComments -> DeclarationWithComments -> Bool)
-> (DeclarationWithComments -> DeclarationWithComments -> Bool)
-> (DeclarationWithComments
-> DeclarationWithComments -> DeclarationWithComments)
-> (DeclarationWithComments
-> DeclarationWithComments -> DeclarationWithComments)
-> Ord DeclarationWithComments
DeclarationWithComments -> DeclarationWithComments -> Bool
DeclarationWithComments -> DeclarationWithComments -> Ordering
DeclarationWithComments
-> DeclarationWithComments -> DeclarationWithComments
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DeclarationWithComments -> DeclarationWithComments -> Ordering
compare :: DeclarationWithComments -> DeclarationWithComments -> Ordering
$c< :: DeclarationWithComments -> DeclarationWithComments -> Bool
< :: DeclarationWithComments -> DeclarationWithComments -> Bool
$c<= :: DeclarationWithComments -> DeclarationWithComments -> Bool
<= :: DeclarationWithComments -> DeclarationWithComments -> Bool
$c> :: DeclarationWithComments -> DeclarationWithComments -> Bool
> :: DeclarationWithComments -> DeclarationWithComments -> Bool
$c>= :: DeclarationWithComments -> DeclarationWithComments -> Bool
>= :: DeclarationWithComments -> DeclarationWithComments -> Bool
$cmax :: DeclarationWithComments
-> DeclarationWithComments -> DeclarationWithComments
max :: DeclarationWithComments
-> DeclarationWithComments -> DeclarationWithComments
$cmin :: DeclarationWithComments
-> DeclarationWithComments -> DeclarationWithComments
min :: DeclarationWithComments
-> DeclarationWithComments -> DeclarationWithComments
Ord, ReadPrec [DeclarationWithComments]
ReadPrec DeclarationWithComments
Int -> ReadS DeclarationWithComments
ReadS [DeclarationWithComments]
(Int -> ReadS DeclarationWithComments)
-> ReadS [DeclarationWithComments]
-> ReadPrec DeclarationWithComments
-> ReadPrec [DeclarationWithComments]
-> Read DeclarationWithComments
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DeclarationWithComments
readsPrec :: Int -> ReadS DeclarationWithComments
$creadList :: ReadS [DeclarationWithComments]
readList :: ReadS [DeclarationWithComments]
$creadPrec :: ReadPrec DeclarationWithComments
readPrec :: ReadPrec DeclarationWithComments
$creadListPrec :: ReadPrec [DeclarationWithComments]
readListPrec :: ReadPrec [DeclarationWithComments]
Read, Int -> DeclarationWithComments -> ShowS
[DeclarationWithComments] -> ShowS
DeclarationWithComments -> String
(Int -> DeclarationWithComments -> ShowS)
-> (DeclarationWithComments -> String)
-> ([DeclarationWithComments] -> ShowS)
-> Show DeclarationWithComments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeclarationWithComments -> ShowS
showsPrec :: Int -> DeclarationWithComments -> ShowS
$cshow :: DeclarationWithComments -> String
show :: DeclarationWithComments -> String
$cshowList :: [DeclarationWithComments] -> ShowS
showList :: [DeclarationWithComments] -> ShowS
Show)
= (String -> Name
Core.Name String
"hydra/langs/haskell/ast.DeclarationWithComments")
_DeclarationWithComments_body :: Name
_DeclarationWithComments_body = (String -> Name
Core.Name String
"body")
= (String -> Name
Core.Name String
"comments")
data Declaration =
DeclarationData DataDeclaration |
DeclarationType TypeDeclaration |
DeclarationValueBinding ValueBinding |
DeclarationTypedBinding TypedBinding
deriving (Declaration -> Declaration -> Bool
(Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool) -> Eq Declaration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Declaration -> Declaration -> Bool
== :: Declaration -> Declaration -> Bool
$c/= :: Declaration -> Declaration -> Bool
/= :: Declaration -> Declaration -> Bool
Eq, Eq Declaration
Eq Declaration =>
(Declaration -> Declaration -> Ordering)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Declaration)
-> (Declaration -> Declaration -> Declaration)
-> Ord Declaration
Declaration -> Declaration -> Bool
Declaration -> Declaration -> Ordering
Declaration -> Declaration -> Declaration
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Declaration -> Declaration -> Ordering
compare :: Declaration -> Declaration -> Ordering
$c< :: Declaration -> Declaration -> Bool
< :: Declaration -> Declaration -> Bool
$c<= :: Declaration -> Declaration -> Bool
<= :: Declaration -> Declaration -> Bool
$c> :: Declaration -> Declaration -> Bool
> :: Declaration -> Declaration -> Bool
$c>= :: Declaration -> Declaration -> Bool
>= :: Declaration -> Declaration -> Bool
$cmax :: Declaration -> Declaration -> Declaration
max :: Declaration -> Declaration -> Declaration
$cmin :: Declaration -> Declaration -> Declaration
min :: Declaration -> Declaration -> Declaration
Ord, ReadPrec [Declaration]
ReadPrec Declaration
Int -> ReadS Declaration
ReadS [Declaration]
(Int -> ReadS Declaration)
-> ReadS [Declaration]
-> ReadPrec Declaration
-> ReadPrec [Declaration]
-> Read Declaration
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Declaration
readsPrec :: Int -> ReadS Declaration
$creadList :: ReadS [Declaration]
readList :: ReadS [Declaration]
$creadPrec :: ReadPrec Declaration
readPrec :: ReadPrec Declaration
$creadListPrec :: ReadPrec [Declaration]
readListPrec :: ReadPrec [Declaration]
Read, Int -> Declaration -> ShowS
[Declaration] -> ShowS
Declaration -> String
(Int -> Declaration -> ShowS)
-> (Declaration -> String)
-> ([Declaration] -> ShowS)
-> Show Declaration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Declaration -> ShowS
showsPrec :: Int -> Declaration -> ShowS
$cshow :: Declaration -> String
show :: Declaration -> String
$cshowList :: [Declaration] -> ShowS
showList :: [Declaration] -> ShowS
Show)
_Declaration :: Name
_Declaration = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Declaration")
_Declaration_data :: Name
_Declaration_data = (String -> Name
Core.Name String
"data")
_Declaration_type :: Name
_Declaration_type = (String -> Name
Core.Name String
"type")
_Declaration_valueBinding :: Name
_Declaration_valueBinding = (String -> Name
Core.Name String
"valueBinding")
_Declaration_typedBinding :: Name
_Declaration_typedBinding = (String -> Name
Core.Name String
"typedBinding")
data DeclarationHead =
DeclarationHeadApplication DeclarationHead_Application |
DeclarationHeadParens DeclarationHead |
DeclarationHeadSimple Name
deriving (DeclarationHead -> DeclarationHead -> Bool
(DeclarationHead -> DeclarationHead -> Bool)
-> (DeclarationHead -> DeclarationHead -> Bool)
-> Eq DeclarationHead
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeclarationHead -> DeclarationHead -> Bool
== :: DeclarationHead -> DeclarationHead -> Bool
$c/= :: DeclarationHead -> DeclarationHead -> Bool
/= :: DeclarationHead -> DeclarationHead -> Bool
Eq, Eq DeclarationHead
Eq DeclarationHead =>
(DeclarationHead -> DeclarationHead -> Ordering)
-> (DeclarationHead -> DeclarationHead -> Bool)
-> (DeclarationHead -> DeclarationHead -> Bool)
-> (DeclarationHead -> DeclarationHead -> Bool)
-> (DeclarationHead -> DeclarationHead -> Bool)
-> (DeclarationHead -> DeclarationHead -> DeclarationHead)
-> (DeclarationHead -> DeclarationHead -> DeclarationHead)
-> Ord DeclarationHead
DeclarationHead -> DeclarationHead -> Bool
DeclarationHead -> DeclarationHead -> Ordering
DeclarationHead -> DeclarationHead -> DeclarationHead
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DeclarationHead -> DeclarationHead -> Ordering
compare :: DeclarationHead -> DeclarationHead -> Ordering
$c< :: DeclarationHead -> DeclarationHead -> Bool
< :: DeclarationHead -> DeclarationHead -> Bool
$c<= :: DeclarationHead -> DeclarationHead -> Bool
<= :: DeclarationHead -> DeclarationHead -> Bool
$c> :: DeclarationHead -> DeclarationHead -> Bool
> :: DeclarationHead -> DeclarationHead -> Bool
$c>= :: DeclarationHead -> DeclarationHead -> Bool
>= :: DeclarationHead -> DeclarationHead -> Bool
$cmax :: DeclarationHead -> DeclarationHead -> DeclarationHead
max :: DeclarationHead -> DeclarationHead -> DeclarationHead
$cmin :: DeclarationHead -> DeclarationHead -> DeclarationHead
min :: DeclarationHead -> DeclarationHead -> DeclarationHead
Ord, ReadPrec [DeclarationHead]
ReadPrec DeclarationHead
Int -> ReadS DeclarationHead
ReadS [DeclarationHead]
(Int -> ReadS DeclarationHead)
-> ReadS [DeclarationHead]
-> ReadPrec DeclarationHead
-> ReadPrec [DeclarationHead]
-> Read DeclarationHead
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DeclarationHead
readsPrec :: Int -> ReadS DeclarationHead
$creadList :: ReadS [DeclarationHead]
readList :: ReadS [DeclarationHead]
$creadPrec :: ReadPrec DeclarationHead
readPrec :: ReadPrec DeclarationHead
$creadListPrec :: ReadPrec [DeclarationHead]
readListPrec :: ReadPrec [DeclarationHead]
Read, Int -> DeclarationHead -> ShowS
[DeclarationHead] -> ShowS
DeclarationHead -> String
(Int -> DeclarationHead -> ShowS)
-> (DeclarationHead -> String)
-> ([DeclarationHead] -> ShowS)
-> Show DeclarationHead
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeclarationHead -> ShowS
showsPrec :: Int -> DeclarationHead -> ShowS
$cshow :: DeclarationHead -> String
show :: DeclarationHead -> String
$cshowList :: [DeclarationHead] -> ShowS
showList :: [DeclarationHead] -> ShowS
Show)
_DeclarationHead :: Name
_DeclarationHead = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.DeclarationHead")
_DeclarationHead_application :: Name
_DeclarationHead_application = (String -> Name
Core.Name String
"application")
_DeclarationHead_parens :: Name
_DeclarationHead_parens = (String -> Name
Core.Name String
"parens")
_DeclarationHead_simple :: Name
_DeclarationHead_simple = (String -> Name
Core.Name String
"simple")
data DeclarationHead_Application =
DeclarationHead_Application {
DeclarationHead_Application -> DeclarationHead
declarationHead_ApplicationFunction :: DeclarationHead,
DeclarationHead_Application -> Variable
declarationHead_ApplicationOperand :: Variable}
deriving (DeclarationHead_Application -> DeclarationHead_Application -> Bool
(DeclarationHead_Application
-> DeclarationHead_Application -> Bool)
-> (DeclarationHead_Application
-> DeclarationHead_Application -> Bool)
-> Eq DeclarationHead_Application
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
== :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
$c/= :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
/= :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
Eq, Eq DeclarationHead_Application
Eq DeclarationHead_Application =>
(DeclarationHead_Application
-> DeclarationHead_Application -> Ordering)
-> (DeclarationHead_Application
-> DeclarationHead_Application -> Bool)
-> (DeclarationHead_Application
-> DeclarationHead_Application -> Bool)
-> (DeclarationHead_Application
-> DeclarationHead_Application -> Bool)
-> (DeclarationHead_Application
-> DeclarationHead_Application -> Bool)
-> (DeclarationHead_Application
-> DeclarationHead_Application -> DeclarationHead_Application)
-> (DeclarationHead_Application
-> DeclarationHead_Application -> DeclarationHead_Application)
-> Ord DeclarationHead_Application
DeclarationHead_Application -> DeclarationHead_Application -> Bool
DeclarationHead_Application
-> DeclarationHead_Application -> Ordering
DeclarationHead_Application
-> DeclarationHead_Application -> DeclarationHead_Application
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DeclarationHead_Application
-> DeclarationHead_Application -> Ordering
compare :: DeclarationHead_Application
-> DeclarationHead_Application -> Ordering
$c< :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
< :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
$c<= :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
<= :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
$c> :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
> :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
$c>= :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
>= :: DeclarationHead_Application -> DeclarationHead_Application -> Bool
$cmax :: DeclarationHead_Application
-> DeclarationHead_Application -> DeclarationHead_Application
max :: DeclarationHead_Application
-> DeclarationHead_Application -> DeclarationHead_Application
$cmin :: DeclarationHead_Application
-> DeclarationHead_Application -> DeclarationHead_Application
min :: DeclarationHead_Application
-> DeclarationHead_Application -> DeclarationHead_Application
Ord, ReadPrec [DeclarationHead_Application]
ReadPrec DeclarationHead_Application
Int -> ReadS DeclarationHead_Application
ReadS [DeclarationHead_Application]
(Int -> ReadS DeclarationHead_Application)
-> ReadS [DeclarationHead_Application]
-> ReadPrec DeclarationHead_Application
-> ReadPrec [DeclarationHead_Application]
-> Read DeclarationHead_Application
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DeclarationHead_Application
readsPrec :: Int -> ReadS DeclarationHead_Application
$creadList :: ReadS [DeclarationHead_Application]
readList :: ReadS [DeclarationHead_Application]
$creadPrec :: ReadPrec DeclarationHead_Application
readPrec :: ReadPrec DeclarationHead_Application
$creadListPrec :: ReadPrec [DeclarationHead_Application]
readListPrec :: ReadPrec [DeclarationHead_Application]
Read, Int -> DeclarationHead_Application -> ShowS
[DeclarationHead_Application] -> ShowS
DeclarationHead_Application -> String
(Int -> DeclarationHead_Application -> ShowS)
-> (DeclarationHead_Application -> String)
-> ([DeclarationHead_Application] -> ShowS)
-> Show DeclarationHead_Application
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeclarationHead_Application -> ShowS
showsPrec :: Int -> DeclarationHead_Application -> ShowS
$cshow :: DeclarationHead_Application -> String
show :: DeclarationHead_Application -> String
$cshowList :: [DeclarationHead_Application] -> ShowS
showList :: [DeclarationHead_Application] -> ShowS
Show)
_DeclarationHead_Application :: Name
_DeclarationHead_Application = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.DeclarationHead.Application")
_DeclarationHead_Application_function :: Name
_DeclarationHead_Application_function = (String -> Name
Core.Name String
"function")
_DeclarationHead_Application_operand :: Name
_DeclarationHead_Application_operand = (String -> Name
Core.Name String
"operand")
newtype Deriving =
Deriving {
Deriving -> [Name]
unDeriving :: [Name]}
deriving (Deriving -> Deriving -> Bool
(Deriving -> Deriving -> Bool)
-> (Deriving -> Deriving -> Bool) -> Eq Deriving
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Deriving -> Deriving -> Bool
== :: Deriving -> Deriving -> Bool
$c/= :: Deriving -> Deriving -> Bool
/= :: Deriving -> Deriving -> Bool
Eq, Eq Deriving
Eq Deriving =>
(Deriving -> Deriving -> Ordering)
-> (Deriving -> Deriving -> Bool)
-> (Deriving -> Deriving -> Bool)
-> (Deriving -> Deriving -> Bool)
-> (Deriving -> Deriving -> Bool)
-> (Deriving -> Deriving -> Deriving)
-> (Deriving -> Deriving -> Deriving)
-> Ord Deriving
Deriving -> Deriving -> Bool
Deriving -> Deriving -> Ordering
Deriving -> Deriving -> Deriving
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Deriving -> Deriving -> Ordering
compare :: Deriving -> Deriving -> Ordering
$c< :: Deriving -> Deriving -> Bool
< :: Deriving -> Deriving -> Bool
$c<= :: Deriving -> Deriving -> Bool
<= :: Deriving -> Deriving -> Bool
$c> :: Deriving -> Deriving -> Bool
> :: Deriving -> Deriving -> Bool
$c>= :: Deriving -> Deriving -> Bool
>= :: Deriving -> Deriving -> Bool
$cmax :: Deriving -> Deriving -> Deriving
max :: Deriving -> Deriving -> Deriving
$cmin :: Deriving -> Deriving -> Deriving
min :: Deriving -> Deriving -> Deriving
Ord, ReadPrec [Deriving]
ReadPrec Deriving
Int -> ReadS Deriving
ReadS [Deriving]
(Int -> ReadS Deriving)
-> ReadS [Deriving]
-> ReadPrec Deriving
-> ReadPrec [Deriving]
-> Read Deriving
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Deriving
readsPrec :: Int -> ReadS Deriving
$creadList :: ReadS [Deriving]
readList :: ReadS [Deriving]
$creadPrec :: ReadPrec Deriving
readPrec :: ReadPrec Deriving
$creadListPrec :: ReadPrec [Deriving]
readListPrec :: ReadPrec [Deriving]
Read, Int -> Deriving -> ShowS
[Deriving] -> ShowS
Deriving -> String
(Int -> Deriving -> ShowS)
-> (Deriving -> String) -> ([Deriving] -> ShowS) -> Show Deriving
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Deriving -> ShowS
showsPrec :: Int -> Deriving -> ShowS
$cshow :: Deriving -> String
show :: Deriving -> String
$cshowList :: [Deriving] -> ShowS
showList :: [Deriving] -> ShowS
Show)
_Deriving :: Name
_Deriving = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Deriving")
data Export =
ExportDeclaration ImportExportSpec |
ExportModule ModuleName
deriving (Export -> Export -> Bool
(Export -> Export -> Bool)
-> (Export -> Export -> Bool) -> Eq Export
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Export -> Export -> Bool
== :: Export -> Export -> Bool
$c/= :: Export -> Export -> Bool
/= :: Export -> Export -> Bool
Eq, Eq Export
Eq Export =>
(Export -> Export -> Ordering)
-> (Export -> Export -> Bool)
-> (Export -> Export -> Bool)
-> (Export -> Export -> Bool)
-> (Export -> Export -> Bool)
-> (Export -> Export -> Export)
-> (Export -> Export -> Export)
-> Ord Export
Export -> Export -> Bool
Export -> Export -> Ordering
Export -> Export -> Export
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Export -> Export -> Ordering
compare :: Export -> Export -> Ordering
$c< :: Export -> Export -> Bool
< :: Export -> Export -> Bool
$c<= :: Export -> Export -> Bool
<= :: Export -> Export -> Bool
$c> :: Export -> Export -> Bool
> :: Export -> Export -> Bool
$c>= :: Export -> Export -> Bool
>= :: Export -> Export -> Bool
$cmax :: Export -> Export -> Export
max :: Export -> Export -> Export
$cmin :: Export -> Export -> Export
min :: Export -> Export -> Export
Ord, ReadPrec [Export]
ReadPrec Export
Int -> ReadS Export
ReadS [Export]
(Int -> ReadS Export)
-> ReadS [Export]
-> ReadPrec Export
-> ReadPrec [Export]
-> Read Export
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Export
readsPrec :: Int -> ReadS Export
$creadList :: ReadS [Export]
readList :: ReadS [Export]
$creadPrec :: ReadPrec Export
readPrec :: ReadPrec Export
$creadListPrec :: ReadPrec [Export]
readListPrec :: ReadPrec [Export]
Read, Int -> Export -> ShowS
[Export] -> ShowS
Export -> String
(Int -> Export -> ShowS)
-> (Export -> String) -> ([Export] -> ShowS) -> Show Export
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Export -> ShowS
showsPrec :: Int -> Export -> ShowS
$cshow :: Export -> String
show :: Export -> String
$cshowList :: [Export] -> ShowS
showList :: [Export] -> ShowS
Show)
_Export :: Name
_Export = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Export")
_Export_declaration :: Name
_Export_declaration = (String -> Name
Core.Name String
"declaration")
_Export_module :: Name
_Export_module = (String -> Name
Core.Name String
"module")
data Expression =
ExpressionApplication Expression_Application |
ExpressionCase Expression_Case |
ExpressionConstructRecord Expression_ConstructRecord |
ExpressionDo [Statement] |
ExpressionIf Expression_If |
ExpressionInfixApplication Expression_InfixApplication |
ExpressionLiteral Literal |
ExpressionLambda Expression_Lambda |
ExpressionLeftSection Expression_Section |
ExpressionLet Expression_Let |
ExpressionList [Expression] |
ExpressionParens Expression |
ExpressionPrefixApplication Expression_PrefixApplication |
ExpressionRightSection Expression_Section |
ExpressionTuple [Expression] |
ExpressionTypeSignature Expression_TypeSignature |
ExpressionUpdateRecord Expression_UpdateRecord |
ExpressionVariable Name
deriving (Expression -> Expression -> Bool
(Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool) -> Eq Expression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression -> Expression -> Bool
== :: Expression -> Expression -> Bool
$c/= :: Expression -> Expression -> Bool
/= :: Expression -> Expression -> Bool
Eq, Eq Expression
Eq Expression =>
(Expression -> Expression -> Ordering)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Expression)
-> (Expression -> Expression -> Expression)
-> Ord Expression
Expression -> Expression -> Bool
Expression -> Expression -> Ordering
Expression -> Expression -> Expression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression -> Expression -> Ordering
compare :: Expression -> Expression -> Ordering
$c< :: Expression -> Expression -> Bool
< :: Expression -> Expression -> Bool
$c<= :: Expression -> Expression -> Bool
<= :: Expression -> Expression -> Bool
$c> :: Expression -> Expression -> Bool
> :: Expression -> Expression -> Bool
$c>= :: Expression -> Expression -> Bool
>= :: Expression -> Expression -> Bool
$cmax :: Expression -> Expression -> Expression
max :: Expression -> Expression -> Expression
$cmin :: Expression -> Expression -> Expression
min :: Expression -> Expression -> Expression
Ord, ReadPrec [Expression]
ReadPrec Expression
Int -> ReadS Expression
ReadS [Expression]
(Int -> ReadS Expression)
-> ReadS [Expression]
-> ReadPrec Expression
-> ReadPrec [Expression]
-> Read Expression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression
readsPrec :: Int -> ReadS Expression
$creadList :: ReadS [Expression]
readList :: ReadS [Expression]
$creadPrec :: ReadPrec Expression
readPrec :: ReadPrec Expression
$creadListPrec :: ReadPrec [Expression]
readListPrec :: ReadPrec [Expression]
Read, Int -> Expression -> ShowS
[Expression] -> ShowS
Expression -> String
(Int -> Expression -> ShowS)
-> (Expression -> String)
-> ([Expression] -> ShowS)
-> Show Expression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression -> ShowS
showsPrec :: Int -> Expression -> ShowS
$cshow :: Expression -> String
show :: Expression -> String
$cshowList :: [Expression] -> ShowS
showList :: [Expression] -> ShowS
Show)
_Expression :: Name
_Expression = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression")
_Expression_application :: Name
_Expression_application = (String -> Name
Core.Name String
"application")
_Expression_case :: Name
_Expression_case = (String -> Name
Core.Name String
"case")
_Expression_constructRecord :: Name
_Expression_constructRecord = (String -> Name
Core.Name String
"constructRecord")
_Expression_do :: Name
_Expression_do = (String -> Name
Core.Name String
"do")
_Expression_if :: Name
_Expression_if = (String -> Name
Core.Name String
"if")
_Expression_infixApplication :: Name
_Expression_infixApplication = (String -> Name
Core.Name String
"infixApplication")
_Expression_literal :: Name
_Expression_literal = (String -> Name
Core.Name String
"literal")
_Expression_lambda :: Name
_Expression_lambda = (String -> Name
Core.Name String
"lambda")
_Expression_leftSection :: Name
_Expression_leftSection = (String -> Name
Core.Name String
"leftSection")
_Expression_let :: Name
_Expression_let = (String -> Name
Core.Name String
"let")
_Expression_list :: Name
_Expression_list = (String -> Name
Core.Name String
"list")
_Expression_parens :: Name
_Expression_parens = (String -> Name
Core.Name String
"parens")
_Expression_prefixApplication :: Name
_Expression_prefixApplication = (String -> Name
Core.Name String
"prefixApplication")
_Expression_rightSection :: Name
_Expression_rightSection = (String -> Name
Core.Name String
"rightSection")
_Expression_tuple :: Name
_Expression_tuple = (String -> Name
Core.Name String
"tuple")
_Expression_typeSignature :: Name
_Expression_typeSignature = (String -> Name
Core.Name String
"typeSignature")
_Expression_updateRecord :: Name
_Expression_updateRecord = (String -> Name
Core.Name String
"updateRecord")
_Expression_variable :: Name
_Expression_variable = (String -> Name
Core.Name String
"variable")
data Expression_Application =
Expression_Application {
Expression_Application -> Expression
expression_ApplicationFunction :: Expression,
Expression_Application -> Expression
expression_ApplicationArgument :: Expression}
deriving (Expression_Application -> Expression_Application -> Bool
(Expression_Application -> Expression_Application -> Bool)
-> (Expression_Application -> Expression_Application -> Bool)
-> Eq Expression_Application
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression_Application -> Expression_Application -> Bool
== :: Expression_Application -> Expression_Application -> Bool
$c/= :: Expression_Application -> Expression_Application -> Bool
/= :: Expression_Application -> Expression_Application -> Bool
Eq, Eq Expression_Application
Eq Expression_Application =>
(Expression_Application -> Expression_Application -> Ordering)
-> (Expression_Application -> Expression_Application -> Bool)
-> (Expression_Application -> Expression_Application -> Bool)
-> (Expression_Application -> Expression_Application -> Bool)
-> (Expression_Application -> Expression_Application -> Bool)
-> (Expression_Application
-> Expression_Application -> Expression_Application)
-> (Expression_Application
-> Expression_Application -> Expression_Application)
-> Ord Expression_Application
Expression_Application -> Expression_Application -> Bool
Expression_Application -> Expression_Application -> Ordering
Expression_Application
-> Expression_Application -> Expression_Application
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression_Application -> Expression_Application -> Ordering
compare :: Expression_Application -> Expression_Application -> Ordering
$c< :: Expression_Application -> Expression_Application -> Bool
< :: Expression_Application -> Expression_Application -> Bool
$c<= :: Expression_Application -> Expression_Application -> Bool
<= :: Expression_Application -> Expression_Application -> Bool
$c> :: Expression_Application -> Expression_Application -> Bool
> :: Expression_Application -> Expression_Application -> Bool
$c>= :: Expression_Application -> Expression_Application -> Bool
>= :: Expression_Application -> Expression_Application -> Bool
$cmax :: Expression_Application
-> Expression_Application -> Expression_Application
max :: Expression_Application
-> Expression_Application -> Expression_Application
$cmin :: Expression_Application
-> Expression_Application -> Expression_Application
min :: Expression_Application
-> Expression_Application -> Expression_Application
Ord, ReadPrec [Expression_Application]
ReadPrec Expression_Application
Int -> ReadS Expression_Application
ReadS [Expression_Application]
(Int -> ReadS Expression_Application)
-> ReadS [Expression_Application]
-> ReadPrec Expression_Application
-> ReadPrec [Expression_Application]
-> Read Expression_Application
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression_Application
readsPrec :: Int -> ReadS Expression_Application
$creadList :: ReadS [Expression_Application]
readList :: ReadS [Expression_Application]
$creadPrec :: ReadPrec Expression_Application
readPrec :: ReadPrec Expression_Application
$creadListPrec :: ReadPrec [Expression_Application]
readListPrec :: ReadPrec [Expression_Application]
Read, Int -> Expression_Application -> ShowS
[Expression_Application] -> ShowS
Expression_Application -> String
(Int -> Expression_Application -> ShowS)
-> (Expression_Application -> String)
-> ([Expression_Application] -> ShowS)
-> Show Expression_Application
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression_Application -> ShowS
showsPrec :: Int -> Expression_Application -> ShowS
$cshow :: Expression_Application -> String
show :: Expression_Application -> String
$cshowList :: [Expression_Application] -> ShowS
showList :: [Expression_Application] -> ShowS
Show)
_Expression_Application :: Name
_Expression_Application = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression.Application")
_Expression_Application_function :: Name
_Expression_Application_function = (String -> Name
Core.Name String
"function")
_Expression_Application_argument :: Name
_Expression_Application_argument = (String -> Name
Core.Name String
"argument")
data Expression_Case =
Expression_Case {
Expression_Case -> Expression
expression_CaseCase :: Expression,
Expression_Case -> [Alternative]
expression_CaseAlternatives :: [Alternative]}
deriving (Expression_Case -> Expression_Case -> Bool
(Expression_Case -> Expression_Case -> Bool)
-> (Expression_Case -> Expression_Case -> Bool)
-> Eq Expression_Case
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression_Case -> Expression_Case -> Bool
== :: Expression_Case -> Expression_Case -> Bool
$c/= :: Expression_Case -> Expression_Case -> Bool
/= :: Expression_Case -> Expression_Case -> Bool
Eq, Eq Expression_Case
Eq Expression_Case =>
(Expression_Case -> Expression_Case -> Ordering)
-> (Expression_Case -> Expression_Case -> Bool)
-> (Expression_Case -> Expression_Case -> Bool)
-> (Expression_Case -> Expression_Case -> Bool)
-> (Expression_Case -> Expression_Case -> Bool)
-> (Expression_Case -> Expression_Case -> Expression_Case)
-> (Expression_Case -> Expression_Case -> Expression_Case)
-> Ord Expression_Case
Expression_Case -> Expression_Case -> Bool
Expression_Case -> Expression_Case -> Ordering
Expression_Case -> Expression_Case -> Expression_Case
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression_Case -> Expression_Case -> Ordering
compare :: Expression_Case -> Expression_Case -> Ordering
$c< :: Expression_Case -> Expression_Case -> Bool
< :: Expression_Case -> Expression_Case -> Bool
$c<= :: Expression_Case -> Expression_Case -> Bool
<= :: Expression_Case -> Expression_Case -> Bool
$c> :: Expression_Case -> Expression_Case -> Bool
> :: Expression_Case -> Expression_Case -> Bool
$c>= :: Expression_Case -> Expression_Case -> Bool
>= :: Expression_Case -> Expression_Case -> Bool
$cmax :: Expression_Case -> Expression_Case -> Expression_Case
max :: Expression_Case -> Expression_Case -> Expression_Case
$cmin :: Expression_Case -> Expression_Case -> Expression_Case
min :: Expression_Case -> Expression_Case -> Expression_Case
Ord, ReadPrec [Expression_Case]
ReadPrec Expression_Case
Int -> ReadS Expression_Case
ReadS [Expression_Case]
(Int -> ReadS Expression_Case)
-> ReadS [Expression_Case]
-> ReadPrec Expression_Case
-> ReadPrec [Expression_Case]
-> Read Expression_Case
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression_Case
readsPrec :: Int -> ReadS Expression_Case
$creadList :: ReadS [Expression_Case]
readList :: ReadS [Expression_Case]
$creadPrec :: ReadPrec Expression_Case
readPrec :: ReadPrec Expression_Case
$creadListPrec :: ReadPrec [Expression_Case]
readListPrec :: ReadPrec [Expression_Case]
Read, Int -> Expression_Case -> ShowS
[Expression_Case] -> ShowS
Expression_Case -> String
(Int -> Expression_Case -> ShowS)
-> (Expression_Case -> String)
-> ([Expression_Case] -> ShowS)
-> Show Expression_Case
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression_Case -> ShowS
showsPrec :: Int -> Expression_Case -> ShowS
$cshow :: Expression_Case -> String
show :: Expression_Case -> String
$cshowList :: [Expression_Case] -> ShowS
showList :: [Expression_Case] -> ShowS
Show)
_Expression_Case :: Name
_Expression_Case = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression.Case")
_Expression_Case_case :: Name
_Expression_Case_case = (String -> Name
Core.Name String
"case")
_Expression_Case_alternatives :: Name
_Expression_Case_alternatives = (String -> Name
Core.Name String
"alternatives")
data Expression_ConstructRecord =
Expression_ConstructRecord {
Expression_ConstructRecord -> Name
expression_ConstructRecordName :: Name,
Expression_ConstructRecord -> [FieldUpdate]
expression_ConstructRecordFields :: [FieldUpdate]}
deriving (Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
(Expression_ConstructRecord -> Expression_ConstructRecord -> Bool)
-> (Expression_ConstructRecord
-> Expression_ConstructRecord -> Bool)
-> Eq Expression_ConstructRecord
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
== :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
$c/= :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
/= :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
Eq, Eq Expression_ConstructRecord
Eq Expression_ConstructRecord =>
(Expression_ConstructRecord
-> Expression_ConstructRecord -> Ordering)
-> (Expression_ConstructRecord
-> Expression_ConstructRecord -> Bool)
-> (Expression_ConstructRecord
-> Expression_ConstructRecord -> Bool)
-> (Expression_ConstructRecord
-> Expression_ConstructRecord -> Bool)
-> (Expression_ConstructRecord
-> Expression_ConstructRecord -> Bool)
-> (Expression_ConstructRecord
-> Expression_ConstructRecord -> Expression_ConstructRecord)
-> (Expression_ConstructRecord
-> Expression_ConstructRecord -> Expression_ConstructRecord)
-> Ord Expression_ConstructRecord
Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
Expression_ConstructRecord
-> Expression_ConstructRecord -> Ordering
Expression_ConstructRecord
-> Expression_ConstructRecord -> Expression_ConstructRecord
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression_ConstructRecord
-> Expression_ConstructRecord -> Ordering
compare :: Expression_ConstructRecord
-> Expression_ConstructRecord -> Ordering
$c< :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
< :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
$c<= :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
<= :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
$c> :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
> :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
$c>= :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
>= :: Expression_ConstructRecord -> Expression_ConstructRecord -> Bool
$cmax :: Expression_ConstructRecord
-> Expression_ConstructRecord -> Expression_ConstructRecord
max :: Expression_ConstructRecord
-> Expression_ConstructRecord -> Expression_ConstructRecord
$cmin :: Expression_ConstructRecord
-> Expression_ConstructRecord -> Expression_ConstructRecord
min :: Expression_ConstructRecord
-> Expression_ConstructRecord -> Expression_ConstructRecord
Ord, ReadPrec [Expression_ConstructRecord]
ReadPrec Expression_ConstructRecord
Int -> ReadS Expression_ConstructRecord
ReadS [Expression_ConstructRecord]
(Int -> ReadS Expression_ConstructRecord)
-> ReadS [Expression_ConstructRecord]
-> ReadPrec Expression_ConstructRecord
-> ReadPrec [Expression_ConstructRecord]
-> Read Expression_ConstructRecord
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression_ConstructRecord
readsPrec :: Int -> ReadS Expression_ConstructRecord
$creadList :: ReadS [Expression_ConstructRecord]
readList :: ReadS [Expression_ConstructRecord]
$creadPrec :: ReadPrec Expression_ConstructRecord
readPrec :: ReadPrec Expression_ConstructRecord
$creadListPrec :: ReadPrec [Expression_ConstructRecord]
readListPrec :: ReadPrec [Expression_ConstructRecord]
Read, Int -> Expression_ConstructRecord -> ShowS
[Expression_ConstructRecord] -> ShowS
Expression_ConstructRecord -> String
(Int -> Expression_ConstructRecord -> ShowS)
-> (Expression_ConstructRecord -> String)
-> ([Expression_ConstructRecord] -> ShowS)
-> Show Expression_ConstructRecord
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression_ConstructRecord -> ShowS
showsPrec :: Int -> Expression_ConstructRecord -> ShowS
$cshow :: Expression_ConstructRecord -> String
show :: Expression_ConstructRecord -> String
$cshowList :: [Expression_ConstructRecord] -> ShowS
showList :: [Expression_ConstructRecord] -> ShowS
Show)
_Expression_ConstructRecord :: Name
_Expression_ConstructRecord = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression.ConstructRecord")
_Expression_ConstructRecord_name :: Name
_Expression_ConstructRecord_name = (String -> Name
Core.Name String
"name")
_Expression_ConstructRecord_fields :: Name
_Expression_ConstructRecord_fields = (String -> Name
Core.Name String
"fields")
data Expression_If =
Expression_If {
Expression_If -> Expression
expression_IfCondition :: Expression,
Expression_If -> Expression
expression_IfThen :: Expression,
Expression_If -> Expression
expression_IfElse :: Expression}
deriving (Expression_If -> Expression_If -> Bool
(Expression_If -> Expression_If -> Bool)
-> (Expression_If -> Expression_If -> Bool) -> Eq Expression_If
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression_If -> Expression_If -> Bool
== :: Expression_If -> Expression_If -> Bool
$c/= :: Expression_If -> Expression_If -> Bool
/= :: Expression_If -> Expression_If -> Bool
Eq, Eq Expression_If
Eq Expression_If =>
(Expression_If -> Expression_If -> Ordering)
-> (Expression_If -> Expression_If -> Bool)
-> (Expression_If -> Expression_If -> Bool)
-> (Expression_If -> Expression_If -> Bool)
-> (Expression_If -> Expression_If -> Bool)
-> (Expression_If -> Expression_If -> Expression_If)
-> (Expression_If -> Expression_If -> Expression_If)
-> Ord Expression_If
Expression_If -> Expression_If -> Bool
Expression_If -> Expression_If -> Ordering
Expression_If -> Expression_If -> Expression_If
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression_If -> Expression_If -> Ordering
compare :: Expression_If -> Expression_If -> Ordering
$c< :: Expression_If -> Expression_If -> Bool
< :: Expression_If -> Expression_If -> Bool
$c<= :: Expression_If -> Expression_If -> Bool
<= :: Expression_If -> Expression_If -> Bool
$c> :: Expression_If -> Expression_If -> Bool
> :: Expression_If -> Expression_If -> Bool
$c>= :: Expression_If -> Expression_If -> Bool
>= :: Expression_If -> Expression_If -> Bool
$cmax :: Expression_If -> Expression_If -> Expression_If
max :: Expression_If -> Expression_If -> Expression_If
$cmin :: Expression_If -> Expression_If -> Expression_If
min :: Expression_If -> Expression_If -> Expression_If
Ord, ReadPrec [Expression_If]
ReadPrec Expression_If
Int -> ReadS Expression_If
ReadS [Expression_If]
(Int -> ReadS Expression_If)
-> ReadS [Expression_If]
-> ReadPrec Expression_If
-> ReadPrec [Expression_If]
-> Read Expression_If
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression_If
readsPrec :: Int -> ReadS Expression_If
$creadList :: ReadS [Expression_If]
readList :: ReadS [Expression_If]
$creadPrec :: ReadPrec Expression_If
readPrec :: ReadPrec Expression_If
$creadListPrec :: ReadPrec [Expression_If]
readListPrec :: ReadPrec [Expression_If]
Read, Int -> Expression_If -> ShowS
[Expression_If] -> ShowS
Expression_If -> String
(Int -> Expression_If -> ShowS)
-> (Expression_If -> String)
-> ([Expression_If] -> ShowS)
-> Show Expression_If
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression_If -> ShowS
showsPrec :: Int -> Expression_If -> ShowS
$cshow :: Expression_If -> String
show :: Expression_If -> String
$cshowList :: [Expression_If] -> ShowS
showList :: [Expression_If] -> ShowS
Show)
_Expression_If :: Name
_Expression_If = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression.If")
_Expression_If_condition :: Name
_Expression_If_condition = (String -> Name
Core.Name String
"condition")
_Expression_If_then :: Name
_Expression_If_then = (String -> Name
Core.Name String
"then")
_Expression_If_else :: Name
_Expression_If_else = (String -> Name
Core.Name String
"else")
data Expression_InfixApplication =
Expression_InfixApplication {
Expression_InfixApplication -> Expression
expression_InfixApplicationLhs :: Expression,
Expression_InfixApplication -> Operator
expression_InfixApplicationOperator :: Operator,
Expression_InfixApplication -> Expression
expression_InfixApplicationRhs :: Expression}
deriving (Expression_InfixApplication -> Expression_InfixApplication -> Bool
(Expression_InfixApplication
-> Expression_InfixApplication -> Bool)
-> (Expression_InfixApplication
-> Expression_InfixApplication -> Bool)
-> Eq Expression_InfixApplication
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
== :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
$c/= :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
/= :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
Eq, Eq Expression_InfixApplication
Eq Expression_InfixApplication =>
(Expression_InfixApplication
-> Expression_InfixApplication -> Ordering)
-> (Expression_InfixApplication
-> Expression_InfixApplication -> Bool)
-> (Expression_InfixApplication
-> Expression_InfixApplication -> Bool)
-> (Expression_InfixApplication
-> Expression_InfixApplication -> Bool)
-> (Expression_InfixApplication
-> Expression_InfixApplication -> Bool)
-> (Expression_InfixApplication
-> Expression_InfixApplication -> Expression_InfixApplication)
-> (Expression_InfixApplication
-> Expression_InfixApplication -> Expression_InfixApplication)
-> Ord Expression_InfixApplication
Expression_InfixApplication -> Expression_InfixApplication -> Bool
Expression_InfixApplication
-> Expression_InfixApplication -> Ordering
Expression_InfixApplication
-> Expression_InfixApplication -> Expression_InfixApplication
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression_InfixApplication
-> Expression_InfixApplication -> Ordering
compare :: Expression_InfixApplication
-> Expression_InfixApplication -> Ordering
$c< :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
< :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
$c<= :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
<= :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
$c> :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
> :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
$c>= :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
>= :: Expression_InfixApplication -> Expression_InfixApplication -> Bool
$cmax :: Expression_InfixApplication
-> Expression_InfixApplication -> Expression_InfixApplication
max :: Expression_InfixApplication
-> Expression_InfixApplication -> Expression_InfixApplication
$cmin :: Expression_InfixApplication
-> Expression_InfixApplication -> Expression_InfixApplication
min :: Expression_InfixApplication
-> Expression_InfixApplication -> Expression_InfixApplication
Ord, ReadPrec [Expression_InfixApplication]
ReadPrec Expression_InfixApplication
Int -> ReadS Expression_InfixApplication
ReadS [Expression_InfixApplication]
(Int -> ReadS Expression_InfixApplication)
-> ReadS [Expression_InfixApplication]
-> ReadPrec Expression_InfixApplication
-> ReadPrec [Expression_InfixApplication]
-> Read Expression_InfixApplication
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression_InfixApplication
readsPrec :: Int -> ReadS Expression_InfixApplication
$creadList :: ReadS [Expression_InfixApplication]
readList :: ReadS [Expression_InfixApplication]
$creadPrec :: ReadPrec Expression_InfixApplication
readPrec :: ReadPrec Expression_InfixApplication
$creadListPrec :: ReadPrec [Expression_InfixApplication]
readListPrec :: ReadPrec [Expression_InfixApplication]
Read, Int -> Expression_InfixApplication -> ShowS
[Expression_InfixApplication] -> ShowS
Expression_InfixApplication -> String
(Int -> Expression_InfixApplication -> ShowS)
-> (Expression_InfixApplication -> String)
-> ([Expression_InfixApplication] -> ShowS)
-> Show Expression_InfixApplication
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression_InfixApplication -> ShowS
showsPrec :: Int -> Expression_InfixApplication -> ShowS
$cshow :: Expression_InfixApplication -> String
show :: Expression_InfixApplication -> String
$cshowList :: [Expression_InfixApplication] -> ShowS
showList :: [Expression_InfixApplication] -> ShowS
Show)
_Expression_InfixApplication :: Name
_Expression_InfixApplication = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression.InfixApplication")
_Expression_InfixApplication_lhs :: Name
_Expression_InfixApplication_lhs = (String -> Name
Core.Name String
"lhs")
_Expression_InfixApplication_operator :: Name
_Expression_InfixApplication_operator = (String -> Name
Core.Name String
"operator")
_Expression_InfixApplication_rhs :: Name
_Expression_InfixApplication_rhs = (String -> Name
Core.Name String
"rhs")
data Expression_Lambda =
Expression_Lambda {
Expression_Lambda -> [Pattern]
expression_LambdaBindings :: [Pattern],
Expression_Lambda -> Expression
expression_LambdaInner :: Expression}
deriving (Expression_Lambda -> Expression_Lambda -> Bool
(Expression_Lambda -> Expression_Lambda -> Bool)
-> (Expression_Lambda -> Expression_Lambda -> Bool)
-> Eq Expression_Lambda
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression_Lambda -> Expression_Lambda -> Bool
== :: Expression_Lambda -> Expression_Lambda -> Bool
$c/= :: Expression_Lambda -> Expression_Lambda -> Bool
/= :: Expression_Lambda -> Expression_Lambda -> Bool
Eq, Eq Expression_Lambda
Eq Expression_Lambda =>
(Expression_Lambda -> Expression_Lambda -> Ordering)
-> (Expression_Lambda -> Expression_Lambda -> Bool)
-> (Expression_Lambda -> Expression_Lambda -> Bool)
-> (Expression_Lambda -> Expression_Lambda -> Bool)
-> (Expression_Lambda -> Expression_Lambda -> Bool)
-> (Expression_Lambda -> Expression_Lambda -> Expression_Lambda)
-> (Expression_Lambda -> Expression_Lambda -> Expression_Lambda)
-> Ord Expression_Lambda
Expression_Lambda -> Expression_Lambda -> Bool
Expression_Lambda -> Expression_Lambda -> Ordering
Expression_Lambda -> Expression_Lambda -> Expression_Lambda
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression_Lambda -> Expression_Lambda -> Ordering
compare :: Expression_Lambda -> Expression_Lambda -> Ordering
$c< :: Expression_Lambda -> Expression_Lambda -> Bool
< :: Expression_Lambda -> Expression_Lambda -> Bool
$c<= :: Expression_Lambda -> Expression_Lambda -> Bool
<= :: Expression_Lambda -> Expression_Lambda -> Bool
$c> :: Expression_Lambda -> Expression_Lambda -> Bool
> :: Expression_Lambda -> Expression_Lambda -> Bool
$c>= :: Expression_Lambda -> Expression_Lambda -> Bool
>= :: Expression_Lambda -> Expression_Lambda -> Bool
$cmax :: Expression_Lambda -> Expression_Lambda -> Expression_Lambda
max :: Expression_Lambda -> Expression_Lambda -> Expression_Lambda
$cmin :: Expression_Lambda -> Expression_Lambda -> Expression_Lambda
min :: Expression_Lambda -> Expression_Lambda -> Expression_Lambda
Ord, ReadPrec [Expression_Lambda]
ReadPrec Expression_Lambda
Int -> ReadS Expression_Lambda
ReadS [Expression_Lambda]
(Int -> ReadS Expression_Lambda)
-> ReadS [Expression_Lambda]
-> ReadPrec Expression_Lambda
-> ReadPrec [Expression_Lambda]
-> Read Expression_Lambda
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression_Lambda
readsPrec :: Int -> ReadS Expression_Lambda
$creadList :: ReadS [Expression_Lambda]
readList :: ReadS [Expression_Lambda]
$creadPrec :: ReadPrec Expression_Lambda
readPrec :: ReadPrec Expression_Lambda
$creadListPrec :: ReadPrec [Expression_Lambda]
readListPrec :: ReadPrec [Expression_Lambda]
Read, Int -> Expression_Lambda -> ShowS
[Expression_Lambda] -> ShowS
Expression_Lambda -> String
(Int -> Expression_Lambda -> ShowS)
-> (Expression_Lambda -> String)
-> ([Expression_Lambda] -> ShowS)
-> Show Expression_Lambda
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression_Lambda -> ShowS
showsPrec :: Int -> Expression_Lambda -> ShowS
$cshow :: Expression_Lambda -> String
show :: Expression_Lambda -> String
$cshowList :: [Expression_Lambda] -> ShowS
showList :: [Expression_Lambda] -> ShowS
Show)
_Expression_Lambda :: Name
_Expression_Lambda = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression.Lambda")
_Expression_Lambda_bindings :: Name
_Expression_Lambda_bindings = (String -> Name
Core.Name String
"bindings")
_Expression_Lambda_inner :: Name
_Expression_Lambda_inner = (String -> Name
Core.Name String
"inner")
data Expression_Let =
Expression_Let {
Expression_Let -> [LocalBinding]
expression_LetBindings :: [LocalBinding],
Expression_Let -> Expression
expression_LetInner :: Expression}
deriving (Expression_Let -> Expression_Let -> Bool
(Expression_Let -> Expression_Let -> Bool)
-> (Expression_Let -> Expression_Let -> Bool) -> Eq Expression_Let
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression_Let -> Expression_Let -> Bool
== :: Expression_Let -> Expression_Let -> Bool
$c/= :: Expression_Let -> Expression_Let -> Bool
/= :: Expression_Let -> Expression_Let -> Bool
Eq, Eq Expression_Let
Eq Expression_Let =>
(Expression_Let -> Expression_Let -> Ordering)
-> (Expression_Let -> Expression_Let -> Bool)
-> (Expression_Let -> Expression_Let -> Bool)
-> (Expression_Let -> Expression_Let -> Bool)
-> (Expression_Let -> Expression_Let -> Bool)
-> (Expression_Let -> Expression_Let -> Expression_Let)
-> (Expression_Let -> Expression_Let -> Expression_Let)
-> Ord Expression_Let
Expression_Let -> Expression_Let -> Bool
Expression_Let -> Expression_Let -> Ordering
Expression_Let -> Expression_Let -> Expression_Let
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression_Let -> Expression_Let -> Ordering
compare :: Expression_Let -> Expression_Let -> Ordering
$c< :: Expression_Let -> Expression_Let -> Bool
< :: Expression_Let -> Expression_Let -> Bool
$c<= :: Expression_Let -> Expression_Let -> Bool
<= :: Expression_Let -> Expression_Let -> Bool
$c> :: Expression_Let -> Expression_Let -> Bool
> :: Expression_Let -> Expression_Let -> Bool
$c>= :: Expression_Let -> Expression_Let -> Bool
>= :: Expression_Let -> Expression_Let -> Bool
$cmax :: Expression_Let -> Expression_Let -> Expression_Let
max :: Expression_Let -> Expression_Let -> Expression_Let
$cmin :: Expression_Let -> Expression_Let -> Expression_Let
min :: Expression_Let -> Expression_Let -> Expression_Let
Ord, ReadPrec [Expression_Let]
ReadPrec Expression_Let
Int -> ReadS Expression_Let
ReadS [Expression_Let]
(Int -> ReadS Expression_Let)
-> ReadS [Expression_Let]
-> ReadPrec Expression_Let
-> ReadPrec [Expression_Let]
-> Read Expression_Let
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression_Let
readsPrec :: Int -> ReadS Expression_Let
$creadList :: ReadS [Expression_Let]
readList :: ReadS [Expression_Let]
$creadPrec :: ReadPrec Expression_Let
readPrec :: ReadPrec Expression_Let
$creadListPrec :: ReadPrec [Expression_Let]
readListPrec :: ReadPrec [Expression_Let]
Read, Int -> Expression_Let -> ShowS
[Expression_Let] -> ShowS
Expression_Let -> String
(Int -> Expression_Let -> ShowS)
-> (Expression_Let -> String)
-> ([Expression_Let] -> ShowS)
-> Show Expression_Let
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression_Let -> ShowS
showsPrec :: Int -> Expression_Let -> ShowS
$cshow :: Expression_Let -> String
show :: Expression_Let -> String
$cshowList :: [Expression_Let] -> ShowS
showList :: [Expression_Let] -> ShowS
Show)
_Expression_Let :: Name
_Expression_Let = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression.Let")
_Expression_Let_bindings :: Name
_Expression_Let_bindings = (String -> Name
Core.Name String
"bindings")
_Expression_Let_inner :: Name
_Expression_Let_inner = (String -> Name
Core.Name String
"inner")
data Expression_PrefixApplication =
Expression_PrefixApplication {
Expression_PrefixApplication -> Operator
expression_PrefixApplicationOperator :: Operator,
Expression_PrefixApplication -> Expression
expression_PrefixApplicationRhs :: Expression}
deriving (Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
(Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool)
-> (Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool)
-> Eq Expression_PrefixApplication
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
== :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
$c/= :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
/= :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
Eq, Eq Expression_PrefixApplication
Eq Expression_PrefixApplication =>
(Expression_PrefixApplication
-> Expression_PrefixApplication -> Ordering)
-> (Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool)
-> (Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool)
-> (Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool)
-> (Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool)
-> (Expression_PrefixApplication
-> Expression_PrefixApplication -> Expression_PrefixApplication)
-> (Expression_PrefixApplication
-> Expression_PrefixApplication -> Expression_PrefixApplication)
-> Ord Expression_PrefixApplication
Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
Expression_PrefixApplication
-> Expression_PrefixApplication -> Ordering
Expression_PrefixApplication
-> Expression_PrefixApplication -> Expression_PrefixApplication
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Ordering
compare :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Ordering
$c< :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
< :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
$c<= :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
<= :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
$c> :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
> :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
$c>= :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
>= :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Bool
$cmax :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Expression_PrefixApplication
max :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Expression_PrefixApplication
$cmin :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Expression_PrefixApplication
min :: Expression_PrefixApplication
-> Expression_PrefixApplication -> Expression_PrefixApplication
Ord, ReadPrec [Expression_PrefixApplication]
ReadPrec Expression_PrefixApplication
Int -> ReadS Expression_PrefixApplication
ReadS [Expression_PrefixApplication]
(Int -> ReadS Expression_PrefixApplication)
-> ReadS [Expression_PrefixApplication]
-> ReadPrec Expression_PrefixApplication
-> ReadPrec [Expression_PrefixApplication]
-> Read Expression_PrefixApplication
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression_PrefixApplication
readsPrec :: Int -> ReadS Expression_PrefixApplication
$creadList :: ReadS [Expression_PrefixApplication]
readList :: ReadS [Expression_PrefixApplication]
$creadPrec :: ReadPrec Expression_PrefixApplication
readPrec :: ReadPrec Expression_PrefixApplication
$creadListPrec :: ReadPrec [Expression_PrefixApplication]
readListPrec :: ReadPrec [Expression_PrefixApplication]
Read, Int -> Expression_PrefixApplication -> ShowS
[Expression_PrefixApplication] -> ShowS
Expression_PrefixApplication -> String
(Int -> Expression_PrefixApplication -> ShowS)
-> (Expression_PrefixApplication -> String)
-> ([Expression_PrefixApplication] -> ShowS)
-> Show Expression_PrefixApplication
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression_PrefixApplication -> ShowS
showsPrec :: Int -> Expression_PrefixApplication -> ShowS
$cshow :: Expression_PrefixApplication -> String
show :: Expression_PrefixApplication -> String
$cshowList :: [Expression_PrefixApplication] -> ShowS
showList :: [Expression_PrefixApplication] -> ShowS
Show)
_Expression_PrefixApplication :: Name
_Expression_PrefixApplication = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression.PrefixApplication")
_Expression_PrefixApplication_operator :: Name
_Expression_PrefixApplication_operator = (String -> Name
Core.Name String
"operator")
_Expression_PrefixApplication_rhs :: Name
_Expression_PrefixApplication_rhs = (String -> Name
Core.Name String
"rhs")
data Expression_Section =
Expression_Section {
Expression_Section -> Operator
expression_SectionOperator :: Operator,
Expression_Section -> Expression
expression_SectionExpression :: Expression}
deriving (Expression_Section -> Expression_Section -> Bool
(Expression_Section -> Expression_Section -> Bool)
-> (Expression_Section -> Expression_Section -> Bool)
-> Eq Expression_Section
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression_Section -> Expression_Section -> Bool
== :: Expression_Section -> Expression_Section -> Bool
$c/= :: Expression_Section -> Expression_Section -> Bool
/= :: Expression_Section -> Expression_Section -> Bool
Eq, Eq Expression_Section
Eq Expression_Section =>
(Expression_Section -> Expression_Section -> Ordering)
-> (Expression_Section -> Expression_Section -> Bool)
-> (Expression_Section -> Expression_Section -> Bool)
-> (Expression_Section -> Expression_Section -> Bool)
-> (Expression_Section -> Expression_Section -> Bool)
-> (Expression_Section -> Expression_Section -> Expression_Section)
-> (Expression_Section -> Expression_Section -> Expression_Section)
-> Ord Expression_Section
Expression_Section -> Expression_Section -> Bool
Expression_Section -> Expression_Section -> Ordering
Expression_Section -> Expression_Section -> Expression_Section
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression_Section -> Expression_Section -> Ordering
compare :: Expression_Section -> Expression_Section -> Ordering
$c< :: Expression_Section -> Expression_Section -> Bool
< :: Expression_Section -> Expression_Section -> Bool
$c<= :: Expression_Section -> Expression_Section -> Bool
<= :: Expression_Section -> Expression_Section -> Bool
$c> :: Expression_Section -> Expression_Section -> Bool
> :: Expression_Section -> Expression_Section -> Bool
$c>= :: Expression_Section -> Expression_Section -> Bool
>= :: Expression_Section -> Expression_Section -> Bool
$cmax :: Expression_Section -> Expression_Section -> Expression_Section
max :: Expression_Section -> Expression_Section -> Expression_Section
$cmin :: Expression_Section -> Expression_Section -> Expression_Section
min :: Expression_Section -> Expression_Section -> Expression_Section
Ord, ReadPrec [Expression_Section]
ReadPrec Expression_Section
Int -> ReadS Expression_Section
ReadS [Expression_Section]
(Int -> ReadS Expression_Section)
-> ReadS [Expression_Section]
-> ReadPrec Expression_Section
-> ReadPrec [Expression_Section]
-> Read Expression_Section
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression_Section
readsPrec :: Int -> ReadS Expression_Section
$creadList :: ReadS [Expression_Section]
readList :: ReadS [Expression_Section]
$creadPrec :: ReadPrec Expression_Section
readPrec :: ReadPrec Expression_Section
$creadListPrec :: ReadPrec [Expression_Section]
readListPrec :: ReadPrec [Expression_Section]
Read, Int -> Expression_Section -> ShowS
[Expression_Section] -> ShowS
Expression_Section -> String
(Int -> Expression_Section -> ShowS)
-> (Expression_Section -> String)
-> ([Expression_Section] -> ShowS)
-> Show Expression_Section
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression_Section -> ShowS
showsPrec :: Int -> Expression_Section -> ShowS
$cshow :: Expression_Section -> String
show :: Expression_Section -> String
$cshowList :: [Expression_Section] -> ShowS
showList :: [Expression_Section] -> ShowS
Show)
_Expression_Section :: Name
_Expression_Section = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression.Section")
_Expression_Section_operator :: Name
_Expression_Section_operator = (String -> Name
Core.Name String
"operator")
_Expression_Section_expression :: Name
_Expression_Section_expression = (String -> Name
Core.Name String
"expression")
data Expression_TypeSignature =
Expression_TypeSignature {
Expression_TypeSignature -> Expression
expression_TypeSignatureInner :: Expression,
Expression_TypeSignature -> Type
expression_TypeSignatureType :: Type}
deriving (Expression_TypeSignature -> Expression_TypeSignature -> Bool
(Expression_TypeSignature -> Expression_TypeSignature -> Bool)
-> (Expression_TypeSignature -> Expression_TypeSignature -> Bool)
-> Eq Expression_TypeSignature
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
== :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
$c/= :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
/= :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
Eq, Eq Expression_TypeSignature
Eq Expression_TypeSignature =>
(Expression_TypeSignature -> Expression_TypeSignature -> Ordering)
-> (Expression_TypeSignature -> Expression_TypeSignature -> Bool)
-> (Expression_TypeSignature -> Expression_TypeSignature -> Bool)
-> (Expression_TypeSignature -> Expression_TypeSignature -> Bool)
-> (Expression_TypeSignature -> Expression_TypeSignature -> Bool)
-> (Expression_TypeSignature
-> Expression_TypeSignature -> Expression_TypeSignature)
-> (Expression_TypeSignature
-> Expression_TypeSignature -> Expression_TypeSignature)
-> Ord Expression_TypeSignature
Expression_TypeSignature -> Expression_TypeSignature -> Bool
Expression_TypeSignature -> Expression_TypeSignature -> Ordering
Expression_TypeSignature
-> Expression_TypeSignature -> Expression_TypeSignature
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression_TypeSignature -> Expression_TypeSignature -> Ordering
compare :: Expression_TypeSignature -> Expression_TypeSignature -> Ordering
$c< :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
< :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
$c<= :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
<= :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
$c> :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
> :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
$c>= :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
>= :: Expression_TypeSignature -> Expression_TypeSignature -> Bool
$cmax :: Expression_TypeSignature
-> Expression_TypeSignature -> Expression_TypeSignature
max :: Expression_TypeSignature
-> Expression_TypeSignature -> Expression_TypeSignature
$cmin :: Expression_TypeSignature
-> Expression_TypeSignature -> Expression_TypeSignature
min :: Expression_TypeSignature
-> Expression_TypeSignature -> Expression_TypeSignature
Ord, ReadPrec [Expression_TypeSignature]
ReadPrec Expression_TypeSignature
Int -> ReadS Expression_TypeSignature
ReadS [Expression_TypeSignature]
(Int -> ReadS Expression_TypeSignature)
-> ReadS [Expression_TypeSignature]
-> ReadPrec Expression_TypeSignature
-> ReadPrec [Expression_TypeSignature]
-> Read Expression_TypeSignature
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression_TypeSignature
readsPrec :: Int -> ReadS Expression_TypeSignature
$creadList :: ReadS [Expression_TypeSignature]
readList :: ReadS [Expression_TypeSignature]
$creadPrec :: ReadPrec Expression_TypeSignature
readPrec :: ReadPrec Expression_TypeSignature
$creadListPrec :: ReadPrec [Expression_TypeSignature]
readListPrec :: ReadPrec [Expression_TypeSignature]
Read, Int -> Expression_TypeSignature -> ShowS
[Expression_TypeSignature] -> ShowS
Expression_TypeSignature -> String
(Int -> Expression_TypeSignature -> ShowS)
-> (Expression_TypeSignature -> String)
-> ([Expression_TypeSignature] -> ShowS)
-> Show Expression_TypeSignature
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression_TypeSignature -> ShowS
showsPrec :: Int -> Expression_TypeSignature -> ShowS
$cshow :: Expression_TypeSignature -> String
show :: Expression_TypeSignature -> String
$cshowList :: [Expression_TypeSignature] -> ShowS
showList :: [Expression_TypeSignature] -> ShowS
Show)
_Expression_TypeSignature :: Name
_Expression_TypeSignature = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression.TypeSignature")
_Expression_TypeSignature_inner :: Name
_Expression_TypeSignature_inner = (String -> Name
Core.Name String
"inner")
_Expression_TypeSignature_type :: Name
_Expression_TypeSignature_type = (String -> Name
Core.Name String
"type")
data Expression_UpdateRecord =
Expression_UpdateRecord {
Expression_UpdateRecord -> Expression
expression_UpdateRecordInner :: Expression,
Expression_UpdateRecord -> [FieldUpdate]
expression_UpdateRecordFields :: [FieldUpdate]}
deriving (Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
(Expression_UpdateRecord -> Expression_UpdateRecord -> Bool)
-> (Expression_UpdateRecord -> Expression_UpdateRecord -> Bool)
-> Eq Expression_UpdateRecord
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
== :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
$c/= :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
/= :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
Eq, Eq Expression_UpdateRecord
Eq Expression_UpdateRecord =>
(Expression_UpdateRecord -> Expression_UpdateRecord -> Ordering)
-> (Expression_UpdateRecord -> Expression_UpdateRecord -> Bool)
-> (Expression_UpdateRecord -> Expression_UpdateRecord -> Bool)
-> (Expression_UpdateRecord -> Expression_UpdateRecord -> Bool)
-> (Expression_UpdateRecord -> Expression_UpdateRecord -> Bool)
-> (Expression_UpdateRecord
-> Expression_UpdateRecord -> Expression_UpdateRecord)
-> (Expression_UpdateRecord
-> Expression_UpdateRecord -> Expression_UpdateRecord)
-> Ord Expression_UpdateRecord
Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
Expression_UpdateRecord -> Expression_UpdateRecord -> Ordering
Expression_UpdateRecord
-> Expression_UpdateRecord -> Expression_UpdateRecord
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression_UpdateRecord -> Expression_UpdateRecord -> Ordering
compare :: Expression_UpdateRecord -> Expression_UpdateRecord -> Ordering
$c< :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
< :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
$c<= :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
<= :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
$c> :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
> :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
$c>= :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
>= :: Expression_UpdateRecord -> Expression_UpdateRecord -> Bool
$cmax :: Expression_UpdateRecord
-> Expression_UpdateRecord -> Expression_UpdateRecord
max :: Expression_UpdateRecord
-> Expression_UpdateRecord -> Expression_UpdateRecord
$cmin :: Expression_UpdateRecord
-> Expression_UpdateRecord -> Expression_UpdateRecord
min :: Expression_UpdateRecord
-> Expression_UpdateRecord -> Expression_UpdateRecord
Ord, ReadPrec [Expression_UpdateRecord]
ReadPrec Expression_UpdateRecord
Int -> ReadS Expression_UpdateRecord
ReadS [Expression_UpdateRecord]
(Int -> ReadS Expression_UpdateRecord)
-> ReadS [Expression_UpdateRecord]
-> ReadPrec Expression_UpdateRecord
-> ReadPrec [Expression_UpdateRecord]
-> Read Expression_UpdateRecord
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression_UpdateRecord
readsPrec :: Int -> ReadS Expression_UpdateRecord
$creadList :: ReadS [Expression_UpdateRecord]
readList :: ReadS [Expression_UpdateRecord]
$creadPrec :: ReadPrec Expression_UpdateRecord
readPrec :: ReadPrec Expression_UpdateRecord
$creadListPrec :: ReadPrec [Expression_UpdateRecord]
readListPrec :: ReadPrec [Expression_UpdateRecord]
Read, Int -> Expression_UpdateRecord -> ShowS
[Expression_UpdateRecord] -> ShowS
Expression_UpdateRecord -> String
(Int -> Expression_UpdateRecord -> ShowS)
-> (Expression_UpdateRecord -> String)
-> ([Expression_UpdateRecord] -> ShowS)
-> Show Expression_UpdateRecord
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression_UpdateRecord -> ShowS
showsPrec :: Int -> Expression_UpdateRecord -> ShowS
$cshow :: Expression_UpdateRecord -> String
show :: Expression_UpdateRecord -> String
$cshowList :: [Expression_UpdateRecord] -> ShowS
showList :: [Expression_UpdateRecord] -> ShowS
Show)
_Expression_UpdateRecord :: Name
_Expression_UpdateRecord = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Expression.UpdateRecord")
_Expression_UpdateRecord_inner :: Name
_Expression_UpdateRecord_inner = (String -> Name
Core.Name String
"inner")
_Expression_UpdateRecord_fields :: Name
_Expression_UpdateRecord_fields = (String -> Name
Core.Name String
"fields")
data Field =
Field {
Field -> Name
fieldName :: Name,
Field -> Type
fieldType :: Type}
deriving (Field -> Field -> Bool
(Field -> Field -> Bool) -> (Field -> Field -> Bool) -> Eq Field
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Field -> Field -> Bool
== :: Field -> Field -> Bool
$c/= :: Field -> Field -> Bool
/= :: Field -> Field -> Bool
Eq, Eq Field
Eq Field =>
(Field -> Field -> Ordering)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Field)
-> (Field -> Field -> Field)
-> Ord Field
Field -> Field -> Bool
Field -> Field -> Ordering
Field -> Field -> Field
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Field -> Field -> Ordering
compare :: Field -> Field -> Ordering
$c< :: Field -> Field -> Bool
< :: Field -> Field -> Bool
$c<= :: Field -> Field -> Bool
<= :: Field -> Field -> Bool
$c> :: Field -> Field -> Bool
> :: Field -> Field -> Bool
$c>= :: Field -> Field -> Bool
>= :: Field -> Field -> Bool
$cmax :: Field -> Field -> Field
max :: Field -> Field -> Field
$cmin :: Field -> Field -> Field
min :: Field -> Field -> Field
Ord, ReadPrec [Field]
ReadPrec Field
Int -> ReadS Field
ReadS [Field]
(Int -> ReadS Field)
-> ReadS [Field]
-> ReadPrec Field
-> ReadPrec [Field]
-> Read Field
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Field
readsPrec :: Int -> ReadS Field
$creadList :: ReadS [Field]
readList :: ReadS [Field]
$creadPrec :: ReadPrec Field
readPrec :: ReadPrec Field
$creadListPrec :: ReadPrec [Field]
readListPrec :: ReadPrec [Field]
Read, Int -> Field -> ShowS
[Field] -> ShowS
Field -> String
(Int -> Field -> ShowS)
-> (Field -> String) -> ([Field] -> ShowS) -> Show Field
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Field -> ShowS
showsPrec :: Int -> Field -> ShowS
$cshow :: Field -> String
show :: Field -> String
$cshowList :: [Field] -> ShowS
showList :: [Field] -> ShowS
Show)
_Field :: Name
_Field = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Field")
_Field_name :: Name
_Field_name = (String -> Name
Core.Name String
"name")
_Field_type :: Name
_Field_type = (String -> Name
Core.Name String
"type")
data =
{
:: Field,
:: (Maybe String)}
deriving (FieldWithComments -> FieldWithComments -> Bool
(FieldWithComments -> FieldWithComments -> Bool)
-> (FieldWithComments -> FieldWithComments -> Bool)
-> Eq FieldWithComments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldWithComments -> FieldWithComments -> Bool
== :: FieldWithComments -> FieldWithComments -> Bool
$c/= :: FieldWithComments -> FieldWithComments -> Bool
/= :: FieldWithComments -> FieldWithComments -> Bool
Eq, Eq FieldWithComments
Eq FieldWithComments =>
(FieldWithComments -> FieldWithComments -> Ordering)
-> (FieldWithComments -> FieldWithComments -> Bool)
-> (FieldWithComments -> FieldWithComments -> Bool)
-> (FieldWithComments -> FieldWithComments -> Bool)
-> (FieldWithComments -> FieldWithComments -> Bool)
-> (FieldWithComments -> FieldWithComments -> FieldWithComments)
-> (FieldWithComments -> FieldWithComments -> FieldWithComments)
-> Ord FieldWithComments
FieldWithComments -> FieldWithComments -> Bool
FieldWithComments -> FieldWithComments -> Ordering
FieldWithComments -> FieldWithComments -> FieldWithComments
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldWithComments -> FieldWithComments -> Ordering
compare :: FieldWithComments -> FieldWithComments -> Ordering
$c< :: FieldWithComments -> FieldWithComments -> Bool
< :: FieldWithComments -> FieldWithComments -> Bool
$c<= :: FieldWithComments -> FieldWithComments -> Bool
<= :: FieldWithComments -> FieldWithComments -> Bool
$c> :: FieldWithComments -> FieldWithComments -> Bool
> :: FieldWithComments -> FieldWithComments -> Bool
$c>= :: FieldWithComments -> FieldWithComments -> Bool
>= :: FieldWithComments -> FieldWithComments -> Bool
$cmax :: FieldWithComments -> FieldWithComments -> FieldWithComments
max :: FieldWithComments -> FieldWithComments -> FieldWithComments
$cmin :: FieldWithComments -> FieldWithComments -> FieldWithComments
min :: FieldWithComments -> FieldWithComments -> FieldWithComments
Ord, ReadPrec [FieldWithComments]
ReadPrec FieldWithComments
Int -> ReadS FieldWithComments
ReadS [FieldWithComments]
(Int -> ReadS FieldWithComments)
-> ReadS [FieldWithComments]
-> ReadPrec FieldWithComments
-> ReadPrec [FieldWithComments]
-> Read FieldWithComments
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldWithComments
readsPrec :: Int -> ReadS FieldWithComments
$creadList :: ReadS [FieldWithComments]
readList :: ReadS [FieldWithComments]
$creadPrec :: ReadPrec FieldWithComments
readPrec :: ReadPrec FieldWithComments
$creadListPrec :: ReadPrec [FieldWithComments]
readListPrec :: ReadPrec [FieldWithComments]
Read, Int -> FieldWithComments -> ShowS
[FieldWithComments] -> ShowS
FieldWithComments -> String
(Int -> FieldWithComments -> ShowS)
-> (FieldWithComments -> String)
-> ([FieldWithComments] -> ShowS)
-> Show FieldWithComments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldWithComments -> ShowS
showsPrec :: Int -> FieldWithComments -> ShowS
$cshow :: FieldWithComments -> String
show :: FieldWithComments -> String
$cshowList :: [FieldWithComments] -> ShowS
showList :: [FieldWithComments] -> ShowS
Show)
= (String -> Name
Core.Name String
"hydra/langs/haskell/ast.FieldWithComments")
= (String -> Name
Core.Name String
"field")
= (String -> Name
Core.Name String
"comments")
data FieldUpdate =
FieldUpdate {
FieldUpdate -> Name
fieldUpdateName :: Name,
FieldUpdate -> Expression
fieldUpdateValue :: Expression}
deriving (FieldUpdate -> FieldUpdate -> Bool
(FieldUpdate -> FieldUpdate -> Bool)
-> (FieldUpdate -> FieldUpdate -> Bool) -> Eq FieldUpdate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldUpdate -> FieldUpdate -> Bool
== :: FieldUpdate -> FieldUpdate -> Bool
$c/= :: FieldUpdate -> FieldUpdate -> Bool
/= :: FieldUpdate -> FieldUpdate -> Bool
Eq, Eq FieldUpdate
Eq FieldUpdate =>
(FieldUpdate -> FieldUpdate -> Ordering)
-> (FieldUpdate -> FieldUpdate -> Bool)
-> (FieldUpdate -> FieldUpdate -> Bool)
-> (FieldUpdate -> FieldUpdate -> Bool)
-> (FieldUpdate -> FieldUpdate -> Bool)
-> (FieldUpdate -> FieldUpdate -> FieldUpdate)
-> (FieldUpdate -> FieldUpdate -> FieldUpdate)
-> Ord FieldUpdate
FieldUpdate -> FieldUpdate -> Bool
FieldUpdate -> FieldUpdate -> Ordering
FieldUpdate -> FieldUpdate -> FieldUpdate
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldUpdate -> FieldUpdate -> Ordering
compare :: FieldUpdate -> FieldUpdate -> Ordering
$c< :: FieldUpdate -> FieldUpdate -> Bool
< :: FieldUpdate -> FieldUpdate -> Bool
$c<= :: FieldUpdate -> FieldUpdate -> Bool
<= :: FieldUpdate -> FieldUpdate -> Bool
$c> :: FieldUpdate -> FieldUpdate -> Bool
> :: FieldUpdate -> FieldUpdate -> Bool
$c>= :: FieldUpdate -> FieldUpdate -> Bool
>= :: FieldUpdate -> FieldUpdate -> Bool
$cmax :: FieldUpdate -> FieldUpdate -> FieldUpdate
max :: FieldUpdate -> FieldUpdate -> FieldUpdate
$cmin :: FieldUpdate -> FieldUpdate -> FieldUpdate
min :: FieldUpdate -> FieldUpdate -> FieldUpdate
Ord, ReadPrec [FieldUpdate]
ReadPrec FieldUpdate
Int -> ReadS FieldUpdate
ReadS [FieldUpdate]
(Int -> ReadS FieldUpdate)
-> ReadS [FieldUpdate]
-> ReadPrec FieldUpdate
-> ReadPrec [FieldUpdate]
-> Read FieldUpdate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldUpdate
readsPrec :: Int -> ReadS FieldUpdate
$creadList :: ReadS [FieldUpdate]
readList :: ReadS [FieldUpdate]
$creadPrec :: ReadPrec FieldUpdate
readPrec :: ReadPrec FieldUpdate
$creadListPrec :: ReadPrec [FieldUpdate]
readListPrec :: ReadPrec [FieldUpdate]
Read, Int -> FieldUpdate -> ShowS
[FieldUpdate] -> ShowS
FieldUpdate -> String
(Int -> FieldUpdate -> ShowS)
-> (FieldUpdate -> String)
-> ([FieldUpdate] -> ShowS)
-> Show FieldUpdate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldUpdate -> ShowS
showsPrec :: Int -> FieldUpdate -> ShowS
$cshow :: FieldUpdate -> String
show :: FieldUpdate -> String
$cshowList :: [FieldUpdate] -> ShowS
showList :: [FieldUpdate] -> ShowS
Show)
_FieldUpdate :: Name
_FieldUpdate = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.FieldUpdate")
_FieldUpdate_name :: Name
_FieldUpdate_name = (String -> Name
Core.Name String
"name")
_FieldUpdate_value :: Name
_FieldUpdate_value = (String -> Name
Core.Name String
"value")
data Import =
Import {
Import -> Bool
importQualified :: Bool,
Import -> ModuleName
importModule :: ModuleName,
Import -> Maybe ModuleName
importAs :: (Maybe ModuleName),
Import -> Maybe Import_Spec
importSpec :: (Maybe Import_Spec)}
deriving (Import -> Import -> Bool
(Import -> Import -> Bool)
-> (Import -> Import -> Bool) -> Eq Import
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Import -> Import -> Bool
== :: Import -> Import -> Bool
$c/= :: Import -> Import -> Bool
/= :: Import -> Import -> Bool
Eq, Eq Import
Eq Import =>
(Import -> Import -> Ordering)
-> (Import -> Import -> Bool)
-> (Import -> Import -> Bool)
-> (Import -> Import -> Bool)
-> (Import -> Import -> Bool)
-> (Import -> Import -> Import)
-> (Import -> Import -> Import)
-> Ord Import
Import -> Import -> Bool
Import -> Import -> Ordering
Import -> Import -> Import
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Import -> Import -> Ordering
compare :: Import -> Import -> Ordering
$c< :: Import -> Import -> Bool
< :: Import -> Import -> Bool
$c<= :: Import -> Import -> Bool
<= :: Import -> Import -> Bool
$c> :: Import -> Import -> Bool
> :: Import -> Import -> Bool
$c>= :: Import -> Import -> Bool
>= :: Import -> Import -> Bool
$cmax :: Import -> Import -> Import
max :: Import -> Import -> Import
$cmin :: Import -> Import -> Import
min :: Import -> Import -> Import
Ord, ReadPrec [Import]
ReadPrec Import
Int -> ReadS Import
ReadS [Import]
(Int -> ReadS Import)
-> ReadS [Import]
-> ReadPrec Import
-> ReadPrec [Import]
-> Read Import
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Import
readsPrec :: Int -> ReadS Import
$creadList :: ReadS [Import]
readList :: ReadS [Import]
$creadPrec :: ReadPrec Import
readPrec :: ReadPrec Import
$creadListPrec :: ReadPrec [Import]
readListPrec :: ReadPrec [Import]
Read, Int -> Import -> ShowS
[Import] -> ShowS
Import -> String
(Int -> Import -> ShowS)
-> (Import -> String) -> ([Import] -> ShowS) -> Show Import
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Import -> ShowS
showsPrec :: Int -> Import -> ShowS
$cshow :: Import -> String
show :: Import -> String
$cshowList :: [Import] -> ShowS
showList :: [Import] -> ShowS
Show)
_Import :: Name
_Import = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Import")
_Import_qualified :: Name
_Import_qualified = (String -> Name
Core.Name String
"qualified")
_Import_module :: Name
_Import_module = (String -> Name
Core.Name String
"module")
_Import_as :: Name
_Import_as = (String -> Name
Core.Name String
"as")
_Import_spec :: Name
_Import_spec = (String -> Name
Core.Name String
"spec")
data Import_Spec =
Import_SpecList [ImportExportSpec] |
Import_SpecHiding [ImportExportSpec]
deriving (Import_Spec -> Import_Spec -> Bool
(Import_Spec -> Import_Spec -> Bool)
-> (Import_Spec -> Import_Spec -> Bool) -> Eq Import_Spec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Import_Spec -> Import_Spec -> Bool
== :: Import_Spec -> Import_Spec -> Bool
$c/= :: Import_Spec -> Import_Spec -> Bool
/= :: Import_Spec -> Import_Spec -> Bool
Eq, Eq Import_Spec
Eq Import_Spec =>
(Import_Spec -> Import_Spec -> Ordering)
-> (Import_Spec -> Import_Spec -> Bool)
-> (Import_Spec -> Import_Spec -> Bool)
-> (Import_Spec -> Import_Spec -> Bool)
-> (Import_Spec -> Import_Spec -> Bool)
-> (Import_Spec -> Import_Spec -> Import_Spec)
-> (Import_Spec -> Import_Spec -> Import_Spec)
-> Ord Import_Spec
Import_Spec -> Import_Spec -> Bool
Import_Spec -> Import_Spec -> Ordering
Import_Spec -> Import_Spec -> Import_Spec
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Import_Spec -> Import_Spec -> Ordering
compare :: Import_Spec -> Import_Spec -> Ordering
$c< :: Import_Spec -> Import_Spec -> Bool
< :: Import_Spec -> Import_Spec -> Bool
$c<= :: Import_Spec -> Import_Spec -> Bool
<= :: Import_Spec -> Import_Spec -> Bool
$c> :: Import_Spec -> Import_Spec -> Bool
> :: Import_Spec -> Import_Spec -> Bool
$c>= :: Import_Spec -> Import_Spec -> Bool
>= :: Import_Spec -> Import_Spec -> Bool
$cmax :: Import_Spec -> Import_Spec -> Import_Spec
max :: Import_Spec -> Import_Spec -> Import_Spec
$cmin :: Import_Spec -> Import_Spec -> Import_Spec
min :: Import_Spec -> Import_Spec -> Import_Spec
Ord, ReadPrec [Import_Spec]
ReadPrec Import_Spec
Int -> ReadS Import_Spec
ReadS [Import_Spec]
(Int -> ReadS Import_Spec)
-> ReadS [Import_Spec]
-> ReadPrec Import_Spec
-> ReadPrec [Import_Spec]
-> Read Import_Spec
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Import_Spec
readsPrec :: Int -> ReadS Import_Spec
$creadList :: ReadS [Import_Spec]
readList :: ReadS [Import_Spec]
$creadPrec :: ReadPrec Import_Spec
readPrec :: ReadPrec Import_Spec
$creadListPrec :: ReadPrec [Import_Spec]
readListPrec :: ReadPrec [Import_Spec]
Read, Int -> Import_Spec -> ShowS
[Import_Spec] -> ShowS
Import_Spec -> String
(Int -> Import_Spec -> ShowS)
-> (Import_Spec -> String)
-> ([Import_Spec] -> ShowS)
-> Show Import_Spec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Import_Spec -> ShowS
showsPrec :: Int -> Import_Spec -> ShowS
$cshow :: Import_Spec -> String
show :: Import_Spec -> String
$cshowList :: [Import_Spec] -> ShowS
showList :: [Import_Spec] -> ShowS
Show)
_Import_Spec :: Name
_Import_Spec = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Import.Spec")
_Import_Spec_list :: Name
_Import_Spec_list = (String -> Name
Core.Name String
"list")
_Import_Spec_hiding :: Name
_Import_Spec_hiding = (String -> Name
Core.Name String
"hiding")
data ImportModifier =
ImportModifierPattern |
ImportModifierType
deriving (ImportModifier -> ImportModifier -> Bool
(ImportModifier -> ImportModifier -> Bool)
-> (ImportModifier -> ImportModifier -> Bool) -> Eq ImportModifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImportModifier -> ImportModifier -> Bool
== :: ImportModifier -> ImportModifier -> Bool
$c/= :: ImportModifier -> ImportModifier -> Bool
/= :: ImportModifier -> ImportModifier -> Bool
Eq, Eq ImportModifier
Eq ImportModifier =>
(ImportModifier -> ImportModifier -> Ordering)
-> (ImportModifier -> ImportModifier -> Bool)
-> (ImportModifier -> ImportModifier -> Bool)
-> (ImportModifier -> ImportModifier -> Bool)
-> (ImportModifier -> ImportModifier -> Bool)
-> (ImportModifier -> ImportModifier -> ImportModifier)
-> (ImportModifier -> ImportModifier -> ImportModifier)
-> Ord ImportModifier
ImportModifier -> ImportModifier -> Bool
ImportModifier -> ImportModifier -> Ordering
ImportModifier -> ImportModifier -> ImportModifier
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ImportModifier -> ImportModifier -> Ordering
compare :: ImportModifier -> ImportModifier -> Ordering
$c< :: ImportModifier -> ImportModifier -> Bool
< :: ImportModifier -> ImportModifier -> Bool
$c<= :: ImportModifier -> ImportModifier -> Bool
<= :: ImportModifier -> ImportModifier -> Bool
$c> :: ImportModifier -> ImportModifier -> Bool
> :: ImportModifier -> ImportModifier -> Bool
$c>= :: ImportModifier -> ImportModifier -> Bool
>= :: ImportModifier -> ImportModifier -> Bool
$cmax :: ImportModifier -> ImportModifier -> ImportModifier
max :: ImportModifier -> ImportModifier -> ImportModifier
$cmin :: ImportModifier -> ImportModifier -> ImportModifier
min :: ImportModifier -> ImportModifier -> ImportModifier
Ord, ReadPrec [ImportModifier]
ReadPrec ImportModifier
Int -> ReadS ImportModifier
ReadS [ImportModifier]
(Int -> ReadS ImportModifier)
-> ReadS [ImportModifier]
-> ReadPrec ImportModifier
-> ReadPrec [ImportModifier]
-> Read ImportModifier
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ImportModifier
readsPrec :: Int -> ReadS ImportModifier
$creadList :: ReadS [ImportModifier]
readList :: ReadS [ImportModifier]
$creadPrec :: ReadPrec ImportModifier
readPrec :: ReadPrec ImportModifier
$creadListPrec :: ReadPrec [ImportModifier]
readListPrec :: ReadPrec [ImportModifier]
Read, Int -> ImportModifier -> ShowS
[ImportModifier] -> ShowS
ImportModifier -> String
(Int -> ImportModifier -> ShowS)
-> (ImportModifier -> String)
-> ([ImportModifier] -> ShowS)
-> Show ImportModifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ImportModifier -> ShowS
showsPrec :: Int -> ImportModifier -> ShowS
$cshow :: ImportModifier -> String
show :: ImportModifier -> String
$cshowList :: [ImportModifier] -> ShowS
showList :: [ImportModifier] -> ShowS
Show)
_ImportModifier :: Name
_ImportModifier = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.ImportModifier")
_ImportModifier_pattern :: Name
_ImportModifier_pattern = (String -> Name
Core.Name String
"pattern")
_ImportModifier_type :: Name
_ImportModifier_type = (String -> Name
Core.Name String
"type")
data ImportExportSpec =
ImportExportSpec {
ImportExportSpec -> Maybe ImportModifier
importExportSpecModifier :: (Maybe ImportModifier),
ImportExportSpec -> Name
importExportSpecName :: Name,
ImportExportSpec -> Maybe ImportExportSpec_Subspec
importExportSpecSubspec :: (Maybe ImportExportSpec_Subspec)}
deriving (ImportExportSpec -> ImportExportSpec -> Bool
(ImportExportSpec -> ImportExportSpec -> Bool)
-> (ImportExportSpec -> ImportExportSpec -> Bool)
-> Eq ImportExportSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImportExportSpec -> ImportExportSpec -> Bool
== :: ImportExportSpec -> ImportExportSpec -> Bool
$c/= :: ImportExportSpec -> ImportExportSpec -> Bool
/= :: ImportExportSpec -> ImportExportSpec -> Bool
Eq, Eq ImportExportSpec
Eq ImportExportSpec =>
(ImportExportSpec -> ImportExportSpec -> Ordering)
-> (ImportExportSpec -> ImportExportSpec -> Bool)
-> (ImportExportSpec -> ImportExportSpec -> Bool)
-> (ImportExportSpec -> ImportExportSpec -> Bool)
-> (ImportExportSpec -> ImportExportSpec -> Bool)
-> (ImportExportSpec -> ImportExportSpec -> ImportExportSpec)
-> (ImportExportSpec -> ImportExportSpec -> ImportExportSpec)
-> Ord ImportExportSpec
ImportExportSpec -> ImportExportSpec -> Bool
ImportExportSpec -> ImportExportSpec -> Ordering
ImportExportSpec -> ImportExportSpec -> ImportExportSpec
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ImportExportSpec -> ImportExportSpec -> Ordering
compare :: ImportExportSpec -> ImportExportSpec -> Ordering
$c< :: ImportExportSpec -> ImportExportSpec -> Bool
< :: ImportExportSpec -> ImportExportSpec -> Bool
$c<= :: ImportExportSpec -> ImportExportSpec -> Bool
<= :: ImportExportSpec -> ImportExportSpec -> Bool
$c> :: ImportExportSpec -> ImportExportSpec -> Bool
> :: ImportExportSpec -> ImportExportSpec -> Bool
$c>= :: ImportExportSpec -> ImportExportSpec -> Bool
>= :: ImportExportSpec -> ImportExportSpec -> Bool
$cmax :: ImportExportSpec -> ImportExportSpec -> ImportExportSpec
max :: ImportExportSpec -> ImportExportSpec -> ImportExportSpec
$cmin :: ImportExportSpec -> ImportExportSpec -> ImportExportSpec
min :: ImportExportSpec -> ImportExportSpec -> ImportExportSpec
Ord, ReadPrec [ImportExportSpec]
ReadPrec ImportExportSpec
Int -> ReadS ImportExportSpec
ReadS [ImportExportSpec]
(Int -> ReadS ImportExportSpec)
-> ReadS [ImportExportSpec]
-> ReadPrec ImportExportSpec
-> ReadPrec [ImportExportSpec]
-> Read ImportExportSpec
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ImportExportSpec
readsPrec :: Int -> ReadS ImportExportSpec
$creadList :: ReadS [ImportExportSpec]
readList :: ReadS [ImportExportSpec]
$creadPrec :: ReadPrec ImportExportSpec
readPrec :: ReadPrec ImportExportSpec
$creadListPrec :: ReadPrec [ImportExportSpec]
readListPrec :: ReadPrec [ImportExportSpec]
Read, Int -> ImportExportSpec -> ShowS
[ImportExportSpec] -> ShowS
ImportExportSpec -> String
(Int -> ImportExportSpec -> ShowS)
-> (ImportExportSpec -> String)
-> ([ImportExportSpec] -> ShowS)
-> Show ImportExportSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ImportExportSpec -> ShowS
showsPrec :: Int -> ImportExportSpec -> ShowS
$cshow :: ImportExportSpec -> String
show :: ImportExportSpec -> String
$cshowList :: [ImportExportSpec] -> ShowS
showList :: [ImportExportSpec] -> ShowS
Show)
_ImportExportSpec :: Name
_ImportExportSpec = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.ImportExportSpec")
_ImportExportSpec_modifier :: Name
_ImportExportSpec_modifier = (String -> Name
Core.Name String
"modifier")
_ImportExportSpec_name :: Name
_ImportExportSpec_name = (String -> Name
Core.Name String
"name")
_ImportExportSpec_subspec :: Name
_ImportExportSpec_subspec = (String -> Name
Core.Name String
"subspec")
data ImportExportSpec_Subspec =
ImportExportSpec_SubspecAll |
ImportExportSpec_SubspecList [Name]
deriving (ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
(ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool)
-> (ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool)
-> Eq ImportExportSpec_Subspec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
== :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
$c/= :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
/= :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
Eq, Eq ImportExportSpec_Subspec
Eq ImportExportSpec_Subspec =>
(ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Ordering)
-> (ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool)
-> (ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool)
-> (ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool)
-> (ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool)
-> (ImportExportSpec_Subspec
-> ImportExportSpec_Subspec -> ImportExportSpec_Subspec)
-> (ImportExportSpec_Subspec
-> ImportExportSpec_Subspec -> ImportExportSpec_Subspec)
-> Ord ImportExportSpec_Subspec
ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Ordering
ImportExportSpec_Subspec
-> ImportExportSpec_Subspec -> ImportExportSpec_Subspec
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Ordering
compare :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Ordering
$c< :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
< :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
$c<= :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
<= :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
$c> :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
> :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
$c>= :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
>= :: ImportExportSpec_Subspec -> ImportExportSpec_Subspec -> Bool
$cmax :: ImportExportSpec_Subspec
-> ImportExportSpec_Subspec -> ImportExportSpec_Subspec
max :: ImportExportSpec_Subspec
-> ImportExportSpec_Subspec -> ImportExportSpec_Subspec
$cmin :: ImportExportSpec_Subspec
-> ImportExportSpec_Subspec -> ImportExportSpec_Subspec
min :: ImportExportSpec_Subspec
-> ImportExportSpec_Subspec -> ImportExportSpec_Subspec
Ord, ReadPrec [ImportExportSpec_Subspec]
ReadPrec ImportExportSpec_Subspec
Int -> ReadS ImportExportSpec_Subspec
ReadS [ImportExportSpec_Subspec]
(Int -> ReadS ImportExportSpec_Subspec)
-> ReadS [ImportExportSpec_Subspec]
-> ReadPrec ImportExportSpec_Subspec
-> ReadPrec [ImportExportSpec_Subspec]
-> Read ImportExportSpec_Subspec
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ImportExportSpec_Subspec
readsPrec :: Int -> ReadS ImportExportSpec_Subspec
$creadList :: ReadS [ImportExportSpec_Subspec]
readList :: ReadS [ImportExportSpec_Subspec]
$creadPrec :: ReadPrec ImportExportSpec_Subspec
readPrec :: ReadPrec ImportExportSpec_Subspec
$creadListPrec :: ReadPrec [ImportExportSpec_Subspec]
readListPrec :: ReadPrec [ImportExportSpec_Subspec]
Read, Int -> ImportExportSpec_Subspec -> ShowS
[ImportExportSpec_Subspec] -> ShowS
ImportExportSpec_Subspec -> String
(Int -> ImportExportSpec_Subspec -> ShowS)
-> (ImportExportSpec_Subspec -> String)
-> ([ImportExportSpec_Subspec] -> ShowS)
-> Show ImportExportSpec_Subspec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ImportExportSpec_Subspec -> ShowS
showsPrec :: Int -> ImportExportSpec_Subspec -> ShowS
$cshow :: ImportExportSpec_Subspec -> String
show :: ImportExportSpec_Subspec -> String
$cshowList :: [ImportExportSpec_Subspec] -> ShowS
showList :: [ImportExportSpec_Subspec] -> ShowS
Show)
_ImportExportSpec_Subspec :: Name
_ImportExportSpec_Subspec = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.ImportExportSpec.Subspec")
_ImportExportSpec_Subspec_all :: Name
_ImportExportSpec_Subspec_all = (String -> Name
Core.Name String
"all")
_ImportExportSpec_Subspec_list :: Name
_ImportExportSpec_Subspec_list = (String -> Name
Core.Name String
"list")
data Literal =
LiteralChar Int |
LiteralDouble Double |
LiteralFloat Float |
LiteralInt Int |
LiteralInteger Integer |
LiteralString String
deriving (Literal -> Literal -> Bool
(Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool) -> Eq Literal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Literal -> Literal -> Bool
== :: Literal -> Literal -> Bool
$c/= :: Literal -> Literal -> Bool
/= :: Literal -> Literal -> Bool
Eq, Eq Literal
Eq Literal =>
(Literal -> Literal -> Ordering)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Literal)
-> (Literal -> Literal -> Literal)
-> Ord Literal
Literal -> Literal -> Bool
Literal -> Literal -> Ordering
Literal -> Literal -> Literal
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Literal -> Literal -> Ordering
compare :: Literal -> Literal -> Ordering
$c< :: Literal -> Literal -> Bool
< :: Literal -> Literal -> Bool
$c<= :: Literal -> Literal -> Bool
<= :: Literal -> Literal -> Bool
$c> :: Literal -> Literal -> Bool
> :: Literal -> Literal -> Bool
$c>= :: Literal -> Literal -> Bool
>= :: Literal -> Literal -> Bool
$cmax :: Literal -> Literal -> Literal
max :: Literal -> Literal -> Literal
$cmin :: Literal -> Literal -> Literal
min :: Literal -> Literal -> Literal
Ord, ReadPrec [Literal]
ReadPrec Literal
Int -> ReadS Literal
ReadS [Literal]
(Int -> ReadS Literal)
-> ReadS [Literal]
-> ReadPrec Literal
-> ReadPrec [Literal]
-> Read Literal
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Literal
readsPrec :: Int -> ReadS Literal
$creadList :: ReadS [Literal]
readList :: ReadS [Literal]
$creadPrec :: ReadPrec Literal
readPrec :: ReadPrec Literal
$creadListPrec :: ReadPrec [Literal]
readListPrec :: ReadPrec [Literal]
Read, Int -> Literal -> ShowS
[Literal] -> ShowS
Literal -> String
(Int -> Literal -> ShowS)
-> (Literal -> String) -> ([Literal] -> ShowS) -> Show Literal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Literal -> ShowS
showsPrec :: Int -> Literal -> ShowS
$cshow :: Literal -> String
show :: Literal -> String
$cshowList :: [Literal] -> ShowS
showList :: [Literal] -> ShowS
Show)
_Literal :: Name
_Literal = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Literal")
_Literal_char :: Name
_Literal_char = (String -> Name
Core.Name String
"char")
_Literal_double :: Name
_Literal_double = (String -> Name
Core.Name String
"double")
_Literal_float :: Name
_Literal_float = (String -> Name
Core.Name String
"float")
_Literal_int :: Name
_Literal_int = (String -> Name
Core.Name String
"int")
_Literal_integer :: Name
_Literal_integer = (String -> Name
Core.Name String
"integer")
_Literal_string :: Name
_Literal_string = (String -> Name
Core.Name String
"string")
data LocalBinding =
LocalBindingSignature TypeSignature |
LocalBindingValue ValueBinding
deriving (LocalBinding -> LocalBinding -> Bool
(LocalBinding -> LocalBinding -> Bool)
-> (LocalBinding -> LocalBinding -> Bool) -> Eq LocalBinding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LocalBinding -> LocalBinding -> Bool
== :: LocalBinding -> LocalBinding -> Bool
$c/= :: LocalBinding -> LocalBinding -> Bool
/= :: LocalBinding -> LocalBinding -> Bool
Eq, Eq LocalBinding
Eq LocalBinding =>
(LocalBinding -> LocalBinding -> Ordering)
-> (LocalBinding -> LocalBinding -> Bool)
-> (LocalBinding -> LocalBinding -> Bool)
-> (LocalBinding -> LocalBinding -> Bool)
-> (LocalBinding -> LocalBinding -> Bool)
-> (LocalBinding -> LocalBinding -> LocalBinding)
-> (LocalBinding -> LocalBinding -> LocalBinding)
-> Ord LocalBinding
LocalBinding -> LocalBinding -> Bool
LocalBinding -> LocalBinding -> Ordering
LocalBinding -> LocalBinding -> LocalBinding
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LocalBinding -> LocalBinding -> Ordering
compare :: LocalBinding -> LocalBinding -> Ordering
$c< :: LocalBinding -> LocalBinding -> Bool
< :: LocalBinding -> LocalBinding -> Bool
$c<= :: LocalBinding -> LocalBinding -> Bool
<= :: LocalBinding -> LocalBinding -> Bool
$c> :: LocalBinding -> LocalBinding -> Bool
> :: LocalBinding -> LocalBinding -> Bool
$c>= :: LocalBinding -> LocalBinding -> Bool
>= :: LocalBinding -> LocalBinding -> Bool
$cmax :: LocalBinding -> LocalBinding -> LocalBinding
max :: LocalBinding -> LocalBinding -> LocalBinding
$cmin :: LocalBinding -> LocalBinding -> LocalBinding
min :: LocalBinding -> LocalBinding -> LocalBinding
Ord, ReadPrec [LocalBinding]
ReadPrec LocalBinding
Int -> ReadS LocalBinding
ReadS [LocalBinding]
(Int -> ReadS LocalBinding)
-> ReadS [LocalBinding]
-> ReadPrec LocalBinding
-> ReadPrec [LocalBinding]
-> Read LocalBinding
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LocalBinding
readsPrec :: Int -> ReadS LocalBinding
$creadList :: ReadS [LocalBinding]
readList :: ReadS [LocalBinding]
$creadPrec :: ReadPrec LocalBinding
readPrec :: ReadPrec LocalBinding
$creadListPrec :: ReadPrec [LocalBinding]
readListPrec :: ReadPrec [LocalBinding]
Read, Int -> LocalBinding -> ShowS
[LocalBinding] -> ShowS
LocalBinding -> String
(Int -> LocalBinding -> ShowS)
-> (LocalBinding -> String)
-> ([LocalBinding] -> ShowS)
-> Show LocalBinding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LocalBinding -> ShowS
showsPrec :: Int -> LocalBinding -> ShowS
$cshow :: LocalBinding -> String
show :: LocalBinding -> String
$cshowList :: [LocalBinding] -> ShowS
showList :: [LocalBinding] -> ShowS
Show)
_LocalBinding :: Name
_LocalBinding = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.LocalBinding")
_LocalBinding_signature :: Name
_LocalBinding_signature = (String -> Name
Core.Name String
"signature")
_LocalBinding_value :: Name
_LocalBinding_value = (String -> Name
Core.Name String
"value")
newtype LocalBindings =
LocalBindings {
LocalBindings -> [LocalBinding]
unLocalBindings :: [LocalBinding]}
deriving (LocalBindings -> LocalBindings -> Bool
(LocalBindings -> LocalBindings -> Bool)
-> (LocalBindings -> LocalBindings -> Bool) -> Eq LocalBindings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LocalBindings -> LocalBindings -> Bool
== :: LocalBindings -> LocalBindings -> Bool
$c/= :: LocalBindings -> LocalBindings -> Bool
/= :: LocalBindings -> LocalBindings -> Bool
Eq, Eq LocalBindings
Eq LocalBindings =>
(LocalBindings -> LocalBindings -> Ordering)
-> (LocalBindings -> LocalBindings -> Bool)
-> (LocalBindings -> LocalBindings -> Bool)
-> (LocalBindings -> LocalBindings -> Bool)
-> (LocalBindings -> LocalBindings -> Bool)
-> (LocalBindings -> LocalBindings -> LocalBindings)
-> (LocalBindings -> LocalBindings -> LocalBindings)
-> Ord LocalBindings
LocalBindings -> LocalBindings -> Bool
LocalBindings -> LocalBindings -> Ordering
LocalBindings -> LocalBindings -> LocalBindings
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LocalBindings -> LocalBindings -> Ordering
compare :: LocalBindings -> LocalBindings -> Ordering
$c< :: LocalBindings -> LocalBindings -> Bool
< :: LocalBindings -> LocalBindings -> Bool
$c<= :: LocalBindings -> LocalBindings -> Bool
<= :: LocalBindings -> LocalBindings -> Bool
$c> :: LocalBindings -> LocalBindings -> Bool
> :: LocalBindings -> LocalBindings -> Bool
$c>= :: LocalBindings -> LocalBindings -> Bool
>= :: LocalBindings -> LocalBindings -> Bool
$cmax :: LocalBindings -> LocalBindings -> LocalBindings
max :: LocalBindings -> LocalBindings -> LocalBindings
$cmin :: LocalBindings -> LocalBindings -> LocalBindings
min :: LocalBindings -> LocalBindings -> LocalBindings
Ord, ReadPrec [LocalBindings]
ReadPrec LocalBindings
Int -> ReadS LocalBindings
ReadS [LocalBindings]
(Int -> ReadS LocalBindings)
-> ReadS [LocalBindings]
-> ReadPrec LocalBindings
-> ReadPrec [LocalBindings]
-> Read LocalBindings
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LocalBindings
readsPrec :: Int -> ReadS LocalBindings
$creadList :: ReadS [LocalBindings]
readList :: ReadS [LocalBindings]
$creadPrec :: ReadPrec LocalBindings
readPrec :: ReadPrec LocalBindings
$creadListPrec :: ReadPrec [LocalBindings]
readListPrec :: ReadPrec [LocalBindings]
Read, Int -> LocalBindings -> ShowS
[LocalBindings] -> ShowS
LocalBindings -> String
(Int -> LocalBindings -> ShowS)
-> (LocalBindings -> String)
-> ([LocalBindings] -> ShowS)
-> Show LocalBindings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LocalBindings -> ShowS
showsPrec :: Int -> LocalBindings -> ShowS
$cshow :: LocalBindings -> String
show :: LocalBindings -> String
$cshowList :: [LocalBindings] -> ShowS
showList :: [LocalBindings] -> ShowS
Show)
_LocalBindings :: Name
_LocalBindings = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.LocalBindings")
data Module =
Module {
Module -> Maybe ModuleHead
moduleHead :: (Maybe ModuleHead),
Module -> [Import]
moduleImports :: [Import],
Module -> [DeclarationWithComments]
moduleDeclarations :: [DeclarationWithComments]}
deriving (Module -> Module -> Bool
(Module -> Module -> Bool)
-> (Module -> Module -> Bool) -> Eq Module
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Module -> Module -> Bool
== :: Module -> Module -> Bool
$c/= :: Module -> Module -> Bool
/= :: Module -> Module -> Bool
Eq, Eq Module
Eq Module =>
(Module -> Module -> Ordering)
-> (Module -> Module -> Bool)
-> (Module -> Module -> Bool)
-> (Module -> Module -> Bool)
-> (Module -> Module -> Bool)
-> (Module -> Module -> Module)
-> (Module -> Module -> Module)
-> Ord Module
Module -> Module -> Bool
Module -> Module -> Ordering
Module -> Module -> Module
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Module -> Module -> Ordering
compare :: Module -> Module -> Ordering
$c< :: Module -> Module -> Bool
< :: Module -> Module -> Bool
$c<= :: Module -> Module -> Bool
<= :: Module -> Module -> Bool
$c> :: Module -> Module -> Bool
> :: Module -> Module -> Bool
$c>= :: Module -> Module -> Bool
>= :: Module -> Module -> Bool
$cmax :: Module -> Module -> Module
max :: Module -> Module -> Module
$cmin :: Module -> Module -> Module
min :: Module -> Module -> Module
Ord, ReadPrec [Module]
ReadPrec Module
Int -> ReadS Module
ReadS [Module]
(Int -> ReadS Module)
-> ReadS [Module]
-> ReadPrec Module
-> ReadPrec [Module]
-> Read Module
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Module
readsPrec :: Int -> ReadS Module
$creadList :: ReadS [Module]
readList :: ReadS [Module]
$creadPrec :: ReadPrec Module
readPrec :: ReadPrec Module
$creadListPrec :: ReadPrec [Module]
readListPrec :: ReadPrec [Module]
Read, Int -> Module -> ShowS
[Module] -> ShowS
Module -> String
(Int -> Module -> ShowS)
-> (Module -> String) -> ([Module] -> ShowS) -> Show Module
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Module -> ShowS
showsPrec :: Int -> Module -> ShowS
$cshow :: Module -> String
show :: Module -> String
$cshowList :: [Module] -> ShowS
showList :: [Module] -> ShowS
Show)
_Module :: Name
_Module = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Module")
_Module_head :: Name
_Module_head = (String -> Name
Core.Name String
"head")
_Module_imports :: Name
_Module_imports = (String -> Name
Core.Name String
"imports")
_Module_declarations :: Name
_Module_declarations = (String -> Name
Core.Name String
"declarations")
data ModuleHead =
ModuleHead {
:: (Maybe String),
ModuleHead -> ModuleName
moduleHeadName :: ModuleName,
ModuleHead -> [Export]
moduleHeadExports :: [Export]}
deriving (ModuleHead -> ModuleHead -> Bool
(ModuleHead -> ModuleHead -> Bool)
-> (ModuleHead -> ModuleHead -> Bool) -> Eq ModuleHead
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ModuleHead -> ModuleHead -> Bool
== :: ModuleHead -> ModuleHead -> Bool
$c/= :: ModuleHead -> ModuleHead -> Bool
/= :: ModuleHead -> ModuleHead -> Bool
Eq, Eq ModuleHead
Eq ModuleHead =>
(ModuleHead -> ModuleHead -> Ordering)
-> (ModuleHead -> ModuleHead -> Bool)
-> (ModuleHead -> ModuleHead -> Bool)
-> (ModuleHead -> ModuleHead -> Bool)
-> (ModuleHead -> ModuleHead -> Bool)
-> (ModuleHead -> ModuleHead -> ModuleHead)
-> (ModuleHead -> ModuleHead -> ModuleHead)
-> Ord ModuleHead
ModuleHead -> ModuleHead -> Bool
ModuleHead -> ModuleHead -> Ordering
ModuleHead -> ModuleHead -> ModuleHead
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ModuleHead -> ModuleHead -> Ordering
compare :: ModuleHead -> ModuleHead -> Ordering
$c< :: ModuleHead -> ModuleHead -> Bool
< :: ModuleHead -> ModuleHead -> Bool
$c<= :: ModuleHead -> ModuleHead -> Bool
<= :: ModuleHead -> ModuleHead -> Bool
$c> :: ModuleHead -> ModuleHead -> Bool
> :: ModuleHead -> ModuleHead -> Bool
$c>= :: ModuleHead -> ModuleHead -> Bool
>= :: ModuleHead -> ModuleHead -> Bool
$cmax :: ModuleHead -> ModuleHead -> ModuleHead
max :: ModuleHead -> ModuleHead -> ModuleHead
$cmin :: ModuleHead -> ModuleHead -> ModuleHead
min :: ModuleHead -> ModuleHead -> ModuleHead
Ord, ReadPrec [ModuleHead]
ReadPrec ModuleHead
Int -> ReadS ModuleHead
ReadS [ModuleHead]
(Int -> ReadS ModuleHead)
-> ReadS [ModuleHead]
-> ReadPrec ModuleHead
-> ReadPrec [ModuleHead]
-> Read ModuleHead
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ModuleHead
readsPrec :: Int -> ReadS ModuleHead
$creadList :: ReadS [ModuleHead]
readList :: ReadS [ModuleHead]
$creadPrec :: ReadPrec ModuleHead
readPrec :: ReadPrec ModuleHead
$creadListPrec :: ReadPrec [ModuleHead]
readListPrec :: ReadPrec [ModuleHead]
Read, Int -> ModuleHead -> ShowS
[ModuleHead] -> ShowS
ModuleHead -> String
(Int -> ModuleHead -> ShowS)
-> (ModuleHead -> String)
-> ([ModuleHead] -> ShowS)
-> Show ModuleHead
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModuleHead -> ShowS
showsPrec :: Int -> ModuleHead -> ShowS
$cshow :: ModuleHead -> String
show :: ModuleHead -> String
$cshowList :: [ModuleHead] -> ShowS
showList :: [ModuleHead] -> ShowS
Show)
_ModuleHead :: Name
_ModuleHead = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.ModuleHead")
= (String -> Name
Core.Name String
"comments")
_ModuleHead_name :: Name
_ModuleHead_name = (String -> Name
Core.Name String
"name")
_ModuleHead_exports :: Name
_ModuleHead_exports = (String -> Name
Core.Name String
"exports")
newtype ModuleName =
ModuleName {
ModuleName -> String
unModuleName :: String}
deriving (ModuleName -> ModuleName -> Bool
(ModuleName -> ModuleName -> Bool)
-> (ModuleName -> ModuleName -> Bool) -> Eq ModuleName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ModuleName -> ModuleName -> Bool
== :: ModuleName -> ModuleName -> Bool
$c/= :: ModuleName -> ModuleName -> Bool
/= :: ModuleName -> ModuleName -> Bool
Eq, Eq ModuleName
Eq ModuleName =>
(ModuleName -> ModuleName -> Ordering)
-> (ModuleName -> ModuleName -> Bool)
-> (ModuleName -> ModuleName -> Bool)
-> (ModuleName -> ModuleName -> Bool)
-> (ModuleName -> ModuleName -> Bool)
-> (ModuleName -> ModuleName -> ModuleName)
-> (ModuleName -> ModuleName -> ModuleName)
-> Ord ModuleName
ModuleName -> ModuleName -> Bool
ModuleName -> ModuleName -> Ordering
ModuleName -> ModuleName -> ModuleName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ModuleName -> ModuleName -> Ordering
compare :: ModuleName -> ModuleName -> Ordering
$c< :: ModuleName -> ModuleName -> Bool
< :: ModuleName -> ModuleName -> Bool
$c<= :: ModuleName -> ModuleName -> Bool
<= :: ModuleName -> ModuleName -> Bool
$c> :: ModuleName -> ModuleName -> Bool
> :: ModuleName -> ModuleName -> Bool
$c>= :: ModuleName -> ModuleName -> Bool
>= :: ModuleName -> ModuleName -> Bool
$cmax :: ModuleName -> ModuleName -> ModuleName
max :: ModuleName -> ModuleName -> ModuleName
$cmin :: ModuleName -> ModuleName -> ModuleName
min :: ModuleName -> ModuleName -> ModuleName
Ord, ReadPrec [ModuleName]
ReadPrec ModuleName
Int -> ReadS ModuleName
ReadS [ModuleName]
(Int -> ReadS ModuleName)
-> ReadS [ModuleName]
-> ReadPrec ModuleName
-> ReadPrec [ModuleName]
-> Read ModuleName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ModuleName
readsPrec :: Int -> ReadS ModuleName
$creadList :: ReadS [ModuleName]
readList :: ReadS [ModuleName]
$creadPrec :: ReadPrec ModuleName
readPrec :: ReadPrec ModuleName
$creadListPrec :: ReadPrec [ModuleName]
readListPrec :: ReadPrec [ModuleName]
Read, Int -> ModuleName -> ShowS
[ModuleName] -> ShowS
ModuleName -> String
(Int -> ModuleName -> ShowS)
-> (ModuleName -> String)
-> ([ModuleName] -> ShowS)
-> Show ModuleName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModuleName -> ShowS
showsPrec :: Int -> ModuleName -> ShowS
$cshow :: ModuleName -> String
show :: ModuleName -> String
$cshowList :: [ModuleName] -> ShowS
showList :: [ModuleName] -> ShowS
Show)
_ModuleName :: Name
_ModuleName = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.ModuleName")
data Name =
NameImplicit QualifiedName |
NameNormal QualifiedName |
NameParens QualifiedName
deriving (Name -> Name -> Bool
(Name -> Name -> Bool) -> (Name -> Name -> Bool) -> Eq Name
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
/= :: Name -> Name -> Bool
Eq, Eq Name
Eq Name =>
(Name -> Name -> Ordering)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Name)
-> (Name -> Name -> Name)
-> Ord Name
Name -> Name -> Bool
Name -> Name -> Ordering
Name -> Name -> Name
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Name -> Name -> Ordering
compare :: Name -> Name -> Ordering
$c< :: Name -> Name -> Bool
< :: Name -> Name -> Bool
$c<= :: Name -> Name -> Bool
<= :: Name -> Name -> Bool
$c> :: Name -> Name -> Bool
> :: Name -> Name -> Bool
$c>= :: Name -> Name -> Bool
>= :: Name -> Name -> Bool
$cmax :: Name -> Name -> Name
max :: Name -> Name -> Name
$cmin :: Name -> Name -> Name
min :: Name -> Name -> Name
Ord, ReadPrec [Name]
ReadPrec Name
Int -> ReadS Name
ReadS [Name]
(Int -> ReadS Name)
-> ReadS [Name] -> ReadPrec Name -> ReadPrec [Name] -> Read Name
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Name
readsPrec :: Int -> ReadS Name
$creadList :: ReadS [Name]
readList :: ReadS [Name]
$creadPrec :: ReadPrec Name
readPrec :: ReadPrec Name
$creadListPrec :: ReadPrec [Name]
readListPrec :: ReadPrec [Name]
Read, Int -> Name -> ShowS
[Name] -> ShowS
Name -> String
(Int -> Name -> ShowS)
-> (Name -> String) -> ([Name] -> ShowS) -> Show Name
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Name -> ShowS
showsPrec :: Int -> Name -> ShowS
$cshow :: Name -> String
show :: Name -> String
$cshowList :: [Name] -> ShowS
showList :: [Name] -> ShowS
Show)
_Name :: Name
_Name = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Name")
_Name_implicit :: Name
_Name_implicit = (String -> Name
Core.Name String
"implicit")
_Name_normal :: Name
_Name_normal = (String -> Name
Core.Name String
"normal")
_Name_parens :: Name
_Name_parens = (String -> Name
Core.Name String
"parens")
newtype NamePart =
NamePart {
NamePart -> String
unNamePart :: String}
deriving (NamePart -> NamePart -> Bool
(NamePart -> NamePart -> Bool)
-> (NamePart -> NamePart -> Bool) -> Eq NamePart
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NamePart -> NamePart -> Bool
== :: NamePart -> NamePart -> Bool
$c/= :: NamePart -> NamePart -> Bool
/= :: NamePart -> NamePart -> Bool
Eq, Eq NamePart
Eq NamePart =>
(NamePart -> NamePart -> Ordering)
-> (NamePart -> NamePart -> Bool)
-> (NamePart -> NamePart -> Bool)
-> (NamePart -> NamePart -> Bool)
-> (NamePart -> NamePart -> Bool)
-> (NamePart -> NamePart -> NamePart)
-> (NamePart -> NamePart -> NamePart)
-> Ord NamePart
NamePart -> NamePart -> Bool
NamePart -> NamePart -> Ordering
NamePart -> NamePart -> NamePart
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: NamePart -> NamePart -> Ordering
compare :: NamePart -> NamePart -> Ordering
$c< :: NamePart -> NamePart -> Bool
< :: NamePart -> NamePart -> Bool
$c<= :: NamePart -> NamePart -> Bool
<= :: NamePart -> NamePart -> Bool
$c> :: NamePart -> NamePart -> Bool
> :: NamePart -> NamePart -> Bool
$c>= :: NamePart -> NamePart -> Bool
>= :: NamePart -> NamePart -> Bool
$cmax :: NamePart -> NamePart -> NamePart
max :: NamePart -> NamePart -> NamePart
$cmin :: NamePart -> NamePart -> NamePart
min :: NamePart -> NamePart -> NamePart
Ord, ReadPrec [NamePart]
ReadPrec NamePart
Int -> ReadS NamePart
ReadS [NamePart]
(Int -> ReadS NamePart)
-> ReadS [NamePart]
-> ReadPrec NamePart
-> ReadPrec [NamePart]
-> Read NamePart
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NamePart
readsPrec :: Int -> ReadS NamePart
$creadList :: ReadS [NamePart]
readList :: ReadS [NamePart]
$creadPrec :: ReadPrec NamePart
readPrec :: ReadPrec NamePart
$creadListPrec :: ReadPrec [NamePart]
readListPrec :: ReadPrec [NamePart]
Read, Int -> NamePart -> ShowS
[NamePart] -> ShowS
NamePart -> String
(Int -> NamePart -> ShowS)
-> (NamePart -> String) -> ([NamePart] -> ShowS) -> Show NamePart
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NamePart -> ShowS
showsPrec :: Int -> NamePart -> ShowS
$cshow :: NamePart -> String
show :: NamePart -> String
$cshowList :: [NamePart] -> ShowS
showList :: [NamePart] -> ShowS
Show)
_NamePart :: Name
_NamePart = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.NamePart")
data Operator =
OperatorBacktick QualifiedName |
OperatorNormal QualifiedName
deriving (Operator -> Operator -> Bool
(Operator -> Operator -> Bool)
-> (Operator -> Operator -> Bool) -> Eq Operator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Operator -> Operator -> Bool
== :: Operator -> Operator -> Bool
$c/= :: Operator -> Operator -> Bool
/= :: Operator -> Operator -> Bool
Eq, Eq Operator
Eq Operator =>
(Operator -> Operator -> Ordering)
-> (Operator -> Operator -> Bool)
-> (Operator -> Operator -> Bool)
-> (Operator -> Operator -> Bool)
-> (Operator -> Operator -> Bool)
-> (Operator -> Operator -> Operator)
-> (Operator -> Operator -> Operator)
-> Ord Operator
Operator -> Operator -> Bool
Operator -> Operator -> Ordering
Operator -> Operator -> Operator
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Operator -> Operator -> Ordering
compare :: Operator -> Operator -> Ordering
$c< :: Operator -> Operator -> Bool
< :: Operator -> Operator -> Bool
$c<= :: Operator -> Operator -> Bool
<= :: Operator -> Operator -> Bool
$c> :: Operator -> Operator -> Bool
> :: Operator -> Operator -> Bool
$c>= :: Operator -> Operator -> Bool
>= :: Operator -> Operator -> Bool
$cmax :: Operator -> Operator -> Operator
max :: Operator -> Operator -> Operator
$cmin :: Operator -> Operator -> Operator
min :: Operator -> Operator -> Operator
Ord, ReadPrec [Operator]
ReadPrec Operator
Int -> ReadS Operator
ReadS [Operator]
(Int -> ReadS Operator)
-> ReadS [Operator]
-> ReadPrec Operator
-> ReadPrec [Operator]
-> Read Operator
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Operator
readsPrec :: Int -> ReadS Operator
$creadList :: ReadS [Operator]
readList :: ReadS [Operator]
$creadPrec :: ReadPrec Operator
readPrec :: ReadPrec Operator
$creadListPrec :: ReadPrec [Operator]
readListPrec :: ReadPrec [Operator]
Read, Int -> Operator -> ShowS
[Operator] -> ShowS
Operator -> String
(Int -> Operator -> ShowS)
-> (Operator -> String) -> ([Operator] -> ShowS) -> Show Operator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Operator -> ShowS
showsPrec :: Int -> Operator -> ShowS
$cshow :: Operator -> String
show :: Operator -> String
$cshowList :: [Operator] -> ShowS
showList :: [Operator] -> ShowS
Show)
_Operator :: Name
_Operator = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Operator")
_Operator_backtick :: Name
_Operator_backtick = (String -> Name
Core.Name String
"backtick")
_Operator_normal :: Name
_Operator_normal = (String -> Name
Core.Name String
"normal")
data Pattern =
PatternApplication Pattern_Application |
PatternAs Pattern_As |
PatternList [Pattern] |
PatternLiteral Literal |
PatternName Name |
PatternParens Pattern |
PatternRecord Pattern_Record |
PatternTuple [Pattern] |
PatternTyped Pattern_Typed |
PatternWildcard
deriving (Pattern -> Pattern -> Bool
(Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Bool) -> Eq Pattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pattern -> Pattern -> Bool
== :: Pattern -> Pattern -> Bool
$c/= :: Pattern -> Pattern -> Bool
/= :: Pattern -> Pattern -> Bool
Eq, Eq Pattern
Eq Pattern =>
(Pattern -> Pattern -> Ordering)
-> (Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Pattern)
-> (Pattern -> Pattern -> Pattern)
-> Ord Pattern
Pattern -> Pattern -> Bool
Pattern -> Pattern -> Ordering
Pattern -> Pattern -> Pattern
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Pattern -> Pattern -> Ordering
compare :: Pattern -> Pattern -> Ordering
$c< :: Pattern -> Pattern -> Bool
< :: Pattern -> Pattern -> Bool
$c<= :: Pattern -> Pattern -> Bool
<= :: Pattern -> Pattern -> Bool
$c> :: Pattern -> Pattern -> Bool
> :: Pattern -> Pattern -> Bool
$c>= :: Pattern -> Pattern -> Bool
>= :: Pattern -> Pattern -> Bool
$cmax :: Pattern -> Pattern -> Pattern
max :: Pattern -> Pattern -> Pattern
$cmin :: Pattern -> Pattern -> Pattern
min :: Pattern -> Pattern -> Pattern
Ord, ReadPrec [Pattern]
ReadPrec Pattern
Int -> ReadS Pattern
ReadS [Pattern]
(Int -> ReadS Pattern)
-> ReadS [Pattern]
-> ReadPrec Pattern
-> ReadPrec [Pattern]
-> Read Pattern
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Pattern
readsPrec :: Int -> ReadS Pattern
$creadList :: ReadS [Pattern]
readList :: ReadS [Pattern]
$creadPrec :: ReadPrec Pattern
readPrec :: ReadPrec Pattern
$creadListPrec :: ReadPrec [Pattern]
readListPrec :: ReadPrec [Pattern]
Read, Int -> Pattern -> ShowS
[Pattern] -> ShowS
Pattern -> String
(Int -> Pattern -> ShowS)
-> (Pattern -> String) -> ([Pattern] -> ShowS) -> Show Pattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pattern -> ShowS
showsPrec :: Int -> Pattern -> ShowS
$cshow :: Pattern -> String
show :: Pattern -> String
$cshowList :: [Pattern] -> ShowS
showList :: [Pattern] -> ShowS
Show)
_Pattern :: Name
_Pattern = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Pattern")
_Pattern_application :: Name
_Pattern_application = (String -> Name
Core.Name String
"application")
_Pattern_as :: Name
_Pattern_as = (String -> Name
Core.Name String
"as")
_Pattern_list :: Name
_Pattern_list = (String -> Name
Core.Name String
"list")
_Pattern_literal :: Name
_Pattern_literal = (String -> Name
Core.Name String
"literal")
_Pattern_name :: Name
_Pattern_name = (String -> Name
Core.Name String
"name")
_Pattern_parens :: Name
_Pattern_parens = (String -> Name
Core.Name String
"parens")
_Pattern_record :: Name
_Pattern_record = (String -> Name
Core.Name String
"record")
_Pattern_tuple :: Name
_Pattern_tuple = (String -> Name
Core.Name String
"tuple")
_Pattern_typed :: Name
_Pattern_typed = (String -> Name
Core.Name String
"typed")
_Pattern_wildcard :: Name
_Pattern_wildcard = (String -> Name
Core.Name String
"wildcard")
data Pattern_Application =
Pattern_Application {
Pattern_Application -> Name
pattern_ApplicationName :: Name,
Pattern_Application -> [Pattern]
pattern_ApplicationArgs :: [Pattern]}
deriving (Pattern_Application -> Pattern_Application -> Bool
(Pattern_Application -> Pattern_Application -> Bool)
-> (Pattern_Application -> Pattern_Application -> Bool)
-> Eq Pattern_Application
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pattern_Application -> Pattern_Application -> Bool
== :: Pattern_Application -> Pattern_Application -> Bool
$c/= :: Pattern_Application -> Pattern_Application -> Bool
/= :: Pattern_Application -> Pattern_Application -> Bool
Eq, Eq Pattern_Application
Eq Pattern_Application =>
(Pattern_Application -> Pattern_Application -> Ordering)
-> (Pattern_Application -> Pattern_Application -> Bool)
-> (Pattern_Application -> Pattern_Application -> Bool)
-> (Pattern_Application -> Pattern_Application -> Bool)
-> (Pattern_Application -> Pattern_Application -> Bool)
-> (Pattern_Application
-> Pattern_Application -> Pattern_Application)
-> (Pattern_Application
-> Pattern_Application -> Pattern_Application)
-> Ord Pattern_Application
Pattern_Application -> Pattern_Application -> Bool
Pattern_Application -> Pattern_Application -> Ordering
Pattern_Application -> Pattern_Application -> Pattern_Application
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Pattern_Application -> Pattern_Application -> Ordering
compare :: Pattern_Application -> Pattern_Application -> Ordering
$c< :: Pattern_Application -> Pattern_Application -> Bool
< :: Pattern_Application -> Pattern_Application -> Bool
$c<= :: Pattern_Application -> Pattern_Application -> Bool
<= :: Pattern_Application -> Pattern_Application -> Bool
$c> :: Pattern_Application -> Pattern_Application -> Bool
> :: Pattern_Application -> Pattern_Application -> Bool
$c>= :: Pattern_Application -> Pattern_Application -> Bool
>= :: Pattern_Application -> Pattern_Application -> Bool
$cmax :: Pattern_Application -> Pattern_Application -> Pattern_Application
max :: Pattern_Application -> Pattern_Application -> Pattern_Application
$cmin :: Pattern_Application -> Pattern_Application -> Pattern_Application
min :: Pattern_Application -> Pattern_Application -> Pattern_Application
Ord, ReadPrec [Pattern_Application]
ReadPrec Pattern_Application
Int -> ReadS Pattern_Application
ReadS [Pattern_Application]
(Int -> ReadS Pattern_Application)
-> ReadS [Pattern_Application]
-> ReadPrec Pattern_Application
-> ReadPrec [Pattern_Application]
-> Read Pattern_Application
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Pattern_Application
readsPrec :: Int -> ReadS Pattern_Application
$creadList :: ReadS [Pattern_Application]
readList :: ReadS [Pattern_Application]
$creadPrec :: ReadPrec Pattern_Application
readPrec :: ReadPrec Pattern_Application
$creadListPrec :: ReadPrec [Pattern_Application]
readListPrec :: ReadPrec [Pattern_Application]
Read, Int -> Pattern_Application -> ShowS
[Pattern_Application] -> ShowS
Pattern_Application -> String
(Int -> Pattern_Application -> ShowS)
-> (Pattern_Application -> String)
-> ([Pattern_Application] -> ShowS)
-> Show Pattern_Application
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pattern_Application -> ShowS
showsPrec :: Int -> Pattern_Application -> ShowS
$cshow :: Pattern_Application -> String
show :: Pattern_Application -> String
$cshowList :: [Pattern_Application] -> ShowS
showList :: [Pattern_Application] -> ShowS
Show)
_Pattern_Application :: Name
_Pattern_Application = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Pattern.Application")
_Pattern_Application_name :: Name
_Pattern_Application_name = (String -> Name
Core.Name String
"name")
_Pattern_Application_args :: Name
_Pattern_Application_args = (String -> Name
Core.Name String
"args")
data Pattern_As =
Pattern_As {
Pattern_As -> Name
pattern_AsName :: Name,
Pattern_As -> Pattern
pattern_AsInner :: Pattern}
deriving (Pattern_As -> Pattern_As -> Bool
(Pattern_As -> Pattern_As -> Bool)
-> (Pattern_As -> Pattern_As -> Bool) -> Eq Pattern_As
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pattern_As -> Pattern_As -> Bool
== :: Pattern_As -> Pattern_As -> Bool
$c/= :: Pattern_As -> Pattern_As -> Bool
/= :: Pattern_As -> Pattern_As -> Bool
Eq, Eq Pattern_As
Eq Pattern_As =>
(Pattern_As -> Pattern_As -> Ordering)
-> (Pattern_As -> Pattern_As -> Bool)
-> (Pattern_As -> Pattern_As -> Bool)
-> (Pattern_As -> Pattern_As -> Bool)
-> (Pattern_As -> Pattern_As -> Bool)
-> (Pattern_As -> Pattern_As -> Pattern_As)
-> (Pattern_As -> Pattern_As -> Pattern_As)
-> Ord Pattern_As
Pattern_As -> Pattern_As -> Bool
Pattern_As -> Pattern_As -> Ordering
Pattern_As -> Pattern_As -> Pattern_As
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Pattern_As -> Pattern_As -> Ordering
compare :: Pattern_As -> Pattern_As -> Ordering
$c< :: Pattern_As -> Pattern_As -> Bool
< :: Pattern_As -> Pattern_As -> Bool
$c<= :: Pattern_As -> Pattern_As -> Bool
<= :: Pattern_As -> Pattern_As -> Bool
$c> :: Pattern_As -> Pattern_As -> Bool
> :: Pattern_As -> Pattern_As -> Bool
$c>= :: Pattern_As -> Pattern_As -> Bool
>= :: Pattern_As -> Pattern_As -> Bool
$cmax :: Pattern_As -> Pattern_As -> Pattern_As
max :: Pattern_As -> Pattern_As -> Pattern_As
$cmin :: Pattern_As -> Pattern_As -> Pattern_As
min :: Pattern_As -> Pattern_As -> Pattern_As
Ord, ReadPrec [Pattern_As]
ReadPrec Pattern_As
Int -> ReadS Pattern_As
ReadS [Pattern_As]
(Int -> ReadS Pattern_As)
-> ReadS [Pattern_As]
-> ReadPrec Pattern_As
-> ReadPrec [Pattern_As]
-> Read Pattern_As
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Pattern_As
readsPrec :: Int -> ReadS Pattern_As
$creadList :: ReadS [Pattern_As]
readList :: ReadS [Pattern_As]
$creadPrec :: ReadPrec Pattern_As
readPrec :: ReadPrec Pattern_As
$creadListPrec :: ReadPrec [Pattern_As]
readListPrec :: ReadPrec [Pattern_As]
Read, Int -> Pattern_As -> ShowS
[Pattern_As] -> ShowS
Pattern_As -> String
(Int -> Pattern_As -> ShowS)
-> (Pattern_As -> String)
-> ([Pattern_As] -> ShowS)
-> Show Pattern_As
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pattern_As -> ShowS
showsPrec :: Int -> Pattern_As -> ShowS
$cshow :: Pattern_As -> String
show :: Pattern_As -> String
$cshowList :: [Pattern_As] -> ShowS
showList :: [Pattern_As] -> ShowS
Show)
_Pattern_As :: Name
_Pattern_As = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Pattern.As")
_Pattern_As_name :: Name
_Pattern_As_name = (String -> Name
Core.Name String
"name")
_Pattern_As_inner :: Name
_Pattern_As_inner = (String -> Name
Core.Name String
"inner")
data Pattern_Record =
Pattern_Record {
Pattern_Record -> Name
pattern_RecordName :: Name,
Pattern_Record -> [PatternField]
pattern_RecordFields :: [PatternField]}
deriving (Pattern_Record -> Pattern_Record -> Bool
(Pattern_Record -> Pattern_Record -> Bool)
-> (Pattern_Record -> Pattern_Record -> Bool) -> Eq Pattern_Record
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pattern_Record -> Pattern_Record -> Bool
== :: Pattern_Record -> Pattern_Record -> Bool
$c/= :: Pattern_Record -> Pattern_Record -> Bool
/= :: Pattern_Record -> Pattern_Record -> Bool
Eq, Eq Pattern_Record
Eq Pattern_Record =>
(Pattern_Record -> Pattern_Record -> Ordering)
-> (Pattern_Record -> Pattern_Record -> Bool)
-> (Pattern_Record -> Pattern_Record -> Bool)
-> (Pattern_Record -> Pattern_Record -> Bool)
-> (Pattern_Record -> Pattern_Record -> Bool)
-> (Pattern_Record -> Pattern_Record -> Pattern_Record)
-> (Pattern_Record -> Pattern_Record -> Pattern_Record)
-> Ord Pattern_Record
Pattern_Record -> Pattern_Record -> Bool
Pattern_Record -> Pattern_Record -> Ordering
Pattern_Record -> Pattern_Record -> Pattern_Record
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Pattern_Record -> Pattern_Record -> Ordering
compare :: Pattern_Record -> Pattern_Record -> Ordering
$c< :: Pattern_Record -> Pattern_Record -> Bool
< :: Pattern_Record -> Pattern_Record -> Bool
$c<= :: Pattern_Record -> Pattern_Record -> Bool
<= :: Pattern_Record -> Pattern_Record -> Bool
$c> :: Pattern_Record -> Pattern_Record -> Bool
> :: Pattern_Record -> Pattern_Record -> Bool
$c>= :: Pattern_Record -> Pattern_Record -> Bool
>= :: Pattern_Record -> Pattern_Record -> Bool
$cmax :: Pattern_Record -> Pattern_Record -> Pattern_Record
max :: Pattern_Record -> Pattern_Record -> Pattern_Record
$cmin :: Pattern_Record -> Pattern_Record -> Pattern_Record
min :: Pattern_Record -> Pattern_Record -> Pattern_Record
Ord, ReadPrec [Pattern_Record]
ReadPrec Pattern_Record
Int -> ReadS Pattern_Record
ReadS [Pattern_Record]
(Int -> ReadS Pattern_Record)
-> ReadS [Pattern_Record]
-> ReadPrec Pattern_Record
-> ReadPrec [Pattern_Record]
-> Read Pattern_Record
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Pattern_Record
readsPrec :: Int -> ReadS Pattern_Record
$creadList :: ReadS [Pattern_Record]
readList :: ReadS [Pattern_Record]
$creadPrec :: ReadPrec Pattern_Record
readPrec :: ReadPrec Pattern_Record
$creadListPrec :: ReadPrec [Pattern_Record]
readListPrec :: ReadPrec [Pattern_Record]
Read, Int -> Pattern_Record -> ShowS
[Pattern_Record] -> ShowS
Pattern_Record -> String
(Int -> Pattern_Record -> ShowS)
-> (Pattern_Record -> String)
-> ([Pattern_Record] -> ShowS)
-> Show Pattern_Record
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pattern_Record -> ShowS
showsPrec :: Int -> Pattern_Record -> ShowS
$cshow :: Pattern_Record -> String
show :: Pattern_Record -> String
$cshowList :: [Pattern_Record] -> ShowS
showList :: [Pattern_Record] -> ShowS
Show)
_Pattern_Record :: Name
_Pattern_Record = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Pattern.Record")
_Pattern_Record_name :: Name
_Pattern_Record_name = (String -> Name
Core.Name String
"name")
_Pattern_Record_fields :: Name
_Pattern_Record_fields = (String -> Name
Core.Name String
"fields")
data Pattern_Typed =
Pattern_Typed {
Pattern_Typed -> Pattern
pattern_TypedInner :: Pattern,
Pattern_Typed -> Type
pattern_TypedType :: Type}
deriving (Pattern_Typed -> Pattern_Typed -> Bool
(Pattern_Typed -> Pattern_Typed -> Bool)
-> (Pattern_Typed -> Pattern_Typed -> Bool) -> Eq Pattern_Typed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pattern_Typed -> Pattern_Typed -> Bool
== :: Pattern_Typed -> Pattern_Typed -> Bool
$c/= :: Pattern_Typed -> Pattern_Typed -> Bool
/= :: Pattern_Typed -> Pattern_Typed -> Bool
Eq, Eq Pattern_Typed
Eq Pattern_Typed =>
(Pattern_Typed -> Pattern_Typed -> Ordering)
-> (Pattern_Typed -> Pattern_Typed -> Bool)
-> (Pattern_Typed -> Pattern_Typed -> Bool)
-> (Pattern_Typed -> Pattern_Typed -> Bool)
-> (Pattern_Typed -> Pattern_Typed -> Bool)
-> (Pattern_Typed -> Pattern_Typed -> Pattern_Typed)
-> (Pattern_Typed -> Pattern_Typed -> Pattern_Typed)
-> Ord Pattern_Typed
Pattern_Typed -> Pattern_Typed -> Bool
Pattern_Typed -> Pattern_Typed -> Ordering
Pattern_Typed -> Pattern_Typed -> Pattern_Typed
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Pattern_Typed -> Pattern_Typed -> Ordering
compare :: Pattern_Typed -> Pattern_Typed -> Ordering
$c< :: Pattern_Typed -> Pattern_Typed -> Bool
< :: Pattern_Typed -> Pattern_Typed -> Bool
$c<= :: Pattern_Typed -> Pattern_Typed -> Bool
<= :: Pattern_Typed -> Pattern_Typed -> Bool
$c> :: Pattern_Typed -> Pattern_Typed -> Bool
> :: Pattern_Typed -> Pattern_Typed -> Bool
$c>= :: Pattern_Typed -> Pattern_Typed -> Bool
>= :: Pattern_Typed -> Pattern_Typed -> Bool
$cmax :: Pattern_Typed -> Pattern_Typed -> Pattern_Typed
max :: Pattern_Typed -> Pattern_Typed -> Pattern_Typed
$cmin :: Pattern_Typed -> Pattern_Typed -> Pattern_Typed
min :: Pattern_Typed -> Pattern_Typed -> Pattern_Typed
Ord, ReadPrec [Pattern_Typed]
ReadPrec Pattern_Typed
Int -> ReadS Pattern_Typed
ReadS [Pattern_Typed]
(Int -> ReadS Pattern_Typed)
-> ReadS [Pattern_Typed]
-> ReadPrec Pattern_Typed
-> ReadPrec [Pattern_Typed]
-> Read Pattern_Typed
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Pattern_Typed
readsPrec :: Int -> ReadS Pattern_Typed
$creadList :: ReadS [Pattern_Typed]
readList :: ReadS [Pattern_Typed]
$creadPrec :: ReadPrec Pattern_Typed
readPrec :: ReadPrec Pattern_Typed
$creadListPrec :: ReadPrec [Pattern_Typed]
readListPrec :: ReadPrec [Pattern_Typed]
Read, Int -> Pattern_Typed -> ShowS
[Pattern_Typed] -> ShowS
Pattern_Typed -> String
(Int -> Pattern_Typed -> ShowS)
-> (Pattern_Typed -> String)
-> ([Pattern_Typed] -> ShowS)
-> Show Pattern_Typed
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pattern_Typed -> ShowS
showsPrec :: Int -> Pattern_Typed -> ShowS
$cshow :: Pattern_Typed -> String
show :: Pattern_Typed -> String
$cshowList :: [Pattern_Typed] -> ShowS
showList :: [Pattern_Typed] -> ShowS
Show)
_Pattern_Typed :: Name
_Pattern_Typed = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Pattern.Typed")
_Pattern_Typed_inner :: Name
_Pattern_Typed_inner = (String -> Name
Core.Name String
"inner")
_Pattern_Typed_type :: Name
_Pattern_Typed_type = (String -> Name
Core.Name String
"type")
data PatternField =
PatternField {
PatternField -> Name
patternFieldName :: Name,
PatternField -> Pattern
patternFieldPattern :: Pattern}
deriving (PatternField -> PatternField -> Bool
(PatternField -> PatternField -> Bool)
-> (PatternField -> PatternField -> Bool) -> Eq PatternField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PatternField -> PatternField -> Bool
== :: PatternField -> PatternField -> Bool
$c/= :: PatternField -> PatternField -> Bool
/= :: PatternField -> PatternField -> Bool
Eq, Eq PatternField
Eq PatternField =>
(PatternField -> PatternField -> Ordering)
-> (PatternField -> PatternField -> Bool)
-> (PatternField -> PatternField -> Bool)
-> (PatternField -> PatternField -> Bool)
-> (PatternField -> PatternField -> Bool)
-> (PatternField -> PatternField -> PatternField)
-> (PatternField -> PatternField -> PatternField)
-> Ord PatternField
PatternField -> PatternField -> Bool
PatternField -> PatternField -> Ordering
PatternField -> PatternField -> PatternField
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PatternField -> PatternField -> Ordering
compare :: PatternField -> PatternField -> Ordering
$c< :: PatternField -> PatternField -> Bool
< :: PatternField -> PatternField -> Bool
$c<= :: PatternField -> PatternField -> Bool
<= :: PatternField -> PatternField -> Bool
$c> :: PatternField -> PatternField -> Bool
> :: PatternField -> PatternField -> Bool
$c>= :: PatternField -> PatternField -> Bool
>= :: PatternField -> PatternField -> Bool
$cmax :: PatternField -> PatternField -> PatternField
max :: PatternField -> PatternField -> PatternField
$cmin :: PatternField -> PatternField -> PatternField
min :: PatternField -> PatternField -> PatternField
Ord, ReadPrec [PatternField]
ReadPrec PatternField
Int -> ReadS PatternField
ReadS [PatternField]
(Int -> ReadS PatternField)
-> ReadS [PatternField]
-> ReadPrec PatternField
-> ReadPrec [PatternField]
-> Read PatternField
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PatternField
readsPrec :: Int -> ReadS PatternField
$creadList :: ReadS [PatternField]
readList :: ReadS [PatternField]
$creadPrec :: ReadPrec PatternField
readPrec :: ReadPrec PatternField
$creadListPrec :: ReadPrec [PatternField]
readListPrec :: ReadPrec [PatternField]
Read, Int -> PatternField -> ShowS
[PatternField] -> ShowS
PatternField -> String
(Int -> PatternField -> ShowS)
-> (PatternField -> String)
-> ([PatternField] -> ShowS)
-> Show PatternField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PatternField -> ShowS
showsPrec :: Int -> PatternField -> ShowS
$cshow :: PatternField -> String
show :: PatternField -> String
$cshowList :: [PatternField] -> ShowS
showList :: [PatternField] -> ShowS
Show)
_PatternField :: Name
_PatternField = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.PatternField")
_PatternField_name :: Name
_PatternField_name = (String -> Name
Core.Name String
"name")
_PatternField_pattern :: Name
_PatternField_pattern = (String -> Name
Core.Name String
"pattern")
data QualifiedName =
QualifiedName {
QualifiedName -> [NamePart]
qualifiedNameQualifiers :: [NamePart],
QualifiedName -> NamePart
qualifiedNameUnqualified :: NamePart}
deriving (QualifiedName -> QualifiedName -> Bool
(QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool) -> Eq QualifiedName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QualifiedName -> QualifiedName -> Bool
== :: QualifiedName -> QualifiedName -> Bool
$c/= :: QualifiedName -> QualifiedName -> Bool
/= :: QualifiedName -> QualifiedName -> Bool
Eq, Eq QualifiedName
Eq QualifiedName =>
(QualifiedName -> QualifiedName -> Ordering)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> QualifiedName)
-> (QualifiedName -> QualifiedName -> QualifiedName)
-> Ord QualifiedName
QualifiedName -> QualifiedName -> Bool
QualifiedName -> QualifiedName -> Ordering
QualifiedName -> QualifiedName -> QualifiedName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: QualifiedName -> QualifiedName -> Ordering
compare :: QualifiedName -> QualifiedName -> Ordering
$c< :: QualifiedName -> QualifiedName -> Bool
< :: QualifiedName -> QualifiedName -> Bool
$c<= :: QualifiedName -> QualifiedName -> Bool
<= :: QualifiedName -> QualifiedName -> Bool
$c> :: QualifiedName -> QualifiedName -> Bool
> :: QualifiedName -> QualifiedName -> Bool
$c>= :: QualifiedName -> QualifiedName -> Bool
>= :: QualifiedName -> QualifiedName -> Bool
$cmax :: QualifiedName -> QualifiedName -> QualifiedName
max :: QualifiedName -> QualifiedName -> QualifiedName
$cmin :: QualifiedName -> QualifiedName -> QualifiedName
min :: QualifiedName -> QualifiedName -> QualifiedName
Ord, ReadPrec [QualifiedName]
ReadPrec QualifiedName
Int -> ReadS QualifiedName
ReadS [QualifiedName]
(Int -> ReadS QualifiedName)
-> ReadS [QualifiedName]
-> ReadPrec QualifiedName
-> ReadPrec [QualifiedName]
-> Read QualifiedName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS QualifiedName
readsPrec :: Int -> ReadS QualifiedName
$creadList :: ReadS [QualifiedName]
readList :: ReadS [QualifiedName]
$creadPrec :: ReadPrec QualifiedName
readPrec :: ReadPrec QualifiedName
$creadListPrec :: ReadPrec [QualifiedName]
readListPrec :: ReadPrec [QualifiedName]
Read, Int -> QualifiedName -> ShowS
[QualifiedName] -> ShowS
QualifiedName -> String
(Int -> QualifiedName -> ShowS)
-> (QualifiedName -> String)
-> ([QualifiedName] -> ShowS)
-> Show QualifiedName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QualifiedName -> ShowS
showsPrec :: Int -> QualifiedName -> ShowS
$cshow :: QualifiedName -> String
show :: QualifiedName -> String
$cshowList :: [QualifiedName] -> ShowS
showList :: [QualifiedName] -> ShowS
Show)
_QualifiedName :: Name
_QualifiedName = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.QualifiedName")
_QualifiedName_qualifiers :: Name
_QualifiedName_qualifiers = (String -> Name
Core.Name String
"qualifiers")
_QualifiedName_unqualified :: Name
_QualifiedName_unqualified = (String -> Name
Core.Name String
"unqualified")
newtype RightHandSide =
RightHandSide {
RightHandSide -> Expression
unRightHandSide :: Expression}
deriving (RightHandSide -> RightHandSide -> Bool
(RightHandSide -> RightHandSide -> Bool)
-> (RightHandSide -> RightHandSide -> Bool) -> Eq RightHandSide
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RightHandSide -> RightHandSide -> Bool
== :: RightHandSide -> RightHandSide -> Bool
$c/= :: RightHandSide -> RightHandSide -> Bool
/= :: RightHandSide -> RightHandSide -> Bool
Eq, Eq RightHandSide
Eq RightHandSide =>
(RightHandSide -> RightHandSide -> Ordering)
-> (RightHandSide -> RightHandSide -> Bool)
-> (RightHandSide -> RightHandSide -> Bool)
-> (RightHandSide -> RightHandSide -> Bool)
-> (RightHandSide -> RightHandSide -> Bool)
-> (RightHandSide -> RightHandSide -> RightHandSide)
-> (RightHandSide -> RightHandSide -> RightHandSide)
-> Ord RightHandSide
RightHandSide -> RightHandSide -> Bool
RightHandSide -> RightHandSide -> Ordering
RightHandSide -> RightHandSide -> RightHandSide
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RightHandSide -> RightHandSide -> Ordering
compare :: RightHandSide -> RightHandSide -> Ordering
$c< :: RightHandSide -> RightHandSide -> Bool
< :: RightHandSide -> RightHandSide -> Bool
$c<= :: RightHandSide -> RightHandSide -> Bool
<= :: RightHandSide -> RightHandSide -> Bool
$c> :: RightHandSide -> RightHandSide -> Bool
> :: RightHandSide -> RightHandSide -> Bool
$c>= :: RightHandSide -> RightHandSide -> Bool
>= :: RightHandSide -> RightHandSide -> Bool
$cmax :: RightHandSide -> RightHandSide -> RightHandSide
max :: RightHandSide -> RightHandSide -> RightHandSide
$cmin :: RightHandSide -> RightHandSide -> RightHandSide
min :: RightHandSide -> RightHandSide -> RightHandSide
Ord, ReadPrec [RightHandSide]
ReadPrec RightHandSide
Int -> ReadS RightHandSide
ReadS [RightHandSide]
(Int -> ReadS RightHandSide)
-> ReadS [RightHandSide]
-> ReadPrec RightHandSide
-> ReadPrec [RightHandSide]
-> Read RightHandSide
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RightHandSide
readsPrec :: Int -> ReadS RightHandSide
$creadList :: ReadS [RightHandSide]
readList :: ReadS [RightHandSide]
$creadPrec :: ReadPrec RightHandSide
readPrec :: ReadPrec RightHandSide
$creadListPrec :: ReadPrec [RightHandSide]
readListPrec :: ReadPrec [RightHandSide]
Read, Int -> RightHandSide -> ShowS
[RightHandSide] -> ShowS
RightHandSide -> String
(Int -> RightHandSide -> ShowS)
-> (RightHandSide -> String)
-> ([RightHandSide] -> ShowS)
-> Show RightHandSide
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RightHandSide -> ShowS
showsPrec :: Int -> RightHandSide -> ShowS
$cshow :: RightHandSide -> String
show :: RightHandSide -> String
$cshowList :: [RightHandSide] -> ShowS
showList :: [RightHandSide] -> ShowS
Show)
_RightHandSide :: Name
_RightHandSide = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.RightHandSide")
newtype Statement =
Statement {
Statement -> Expression
unStatement :: Expression}
deriving (Statement -> Statement -> Bool
(Statement -> Statement -> Bool)
-> (Statement -> Statement -> Bool) -> Eq Statement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Statement -> Statement -> Bool
== :: Statement -> Statement -> Bool
$c/= :: Statement -> Statement -> Bool
/= :: Statement -> Statement -> Bool
Eq, Eq Statement
Eq Statement =>
(Statement -> Statement -> Ordering)
-> (Statement -> Statement -> Bool)
-> (Statement -> Statement -> Bool)
-> (Statement -> Statement -> Bool)
-> (Statement -> Statement -> Bool)
-> (Statement -> Statement -> Statement)
-> (Statement -> Statement -> Statement)
-> Ord Statement
Statement -> Statement -> Bool
Statement -> Statement -> Ordering
Statement -> Statement -> Statement
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Statement -> Statement -> Ordering
compare :: Statement -> Statement -> Ordering
$c< :: Statement -> Statement -> Bool
< :: Statement -> Statement -> Bool
$c<= :: Statement -> Statement -> Bool
<= :: Statement -> Statement -> Bool
$c> :: Statement -> Statement -> Bool
> :: Statement -> Statement -> Bool
$c>= :: Statement -> Statement -> Bool
>= :: Statement -> Statement -> Bool
$cmax :: Statement -> Statement -> Statement
max :: Statement -> Statement -> Statement
$cmin :: Statement -> Statement -> Statement
min :: Statement -> Statement -> Statement
Ord, ReadPrec [Statement]
ReadPrec Statement
Int -> ReadS Statement
ReadS [Statement]
(Int -> ReadS Statement)
-> ReadS [Statement]
-> ReadPrec Statement
-> ReadPrec [Statement]
-> Read Statement
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Statement
readsPrec :: Int -> ReadS Statement
$creadList :: ReadS [Statement]
readList :: ReadS [Statement]
$creadPrec :: ReadPrec Statement
readPrec :: ReadPrec Statement
$creadListPrec :: ReadPrec [Statement]
readListPrec :: ReadPrec [Statement]
Read, Int -> Statement -> ShowS
[Statement] -> ShowS
Statement -> String
(Int -> Statement -> ShowS)
-> (Statement -> String)
-> ([Statement] -> ShowS)
-> Show Statement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Statement -> ShowS
showsPrec :: Int -> Statement -> ShowS
$cshow :: Statement -> String
show :: Statement -> String
$cshowList :: [Statement] -> ShowS
showList :: [Statement] -> ShowS
Show)
_Statement :: Name
_Statement = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Statement")
data Type =
TypeApplication Type_Application |
TypeCtx Type_Context |
TypeFunction Type_Function |
TypeInfix Type_Infix |
TypeList Type |
TypeParens Type |
TypeTuple [Type] |
TypeVariable Name
deriving (Type -> Type -> Bool
(Type -> Type -> Bool) -> (Type -> Type -> Bool) -> Eq Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
/= :: Type -> Type -> Bool
Eq, Eq Type
Eq Type =>
(Type -> Type -> Ordering)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Type)
-> (Type -> Type -> Type)
-> Ord Type
Type -> Type -> Bool
Type -> Type -> Ordering
Type -> Type -> Type
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Type -> Type -> Ordering
compare :: Type -> Type -> Ordering
$c< :: Type -> Type -> Bool
< :: Type -> Type -> Bool
$c<= :: Type -> Type -> Bool
<= :: Type -> Type -> Bool
$c> :: Type -> Type -> Bool
> :: Type -> Type -> Bool
$c>= :: Type -> Type -> Bool
>= :: Type -> Type -> Bool
$cmax :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
min :: Type -> Type -> Type
Ord, ReadPrec [Type]
ReadPrec Type
Int -> ReadS Type
ReadS [Type]
(Int -> ReadS Type)
-> ReadS [Type] -> ReadPrec Type -> ReadPrec [Type] -> Read Type
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Type
readsPrec :: Int -> ReadS Type
$creadList :: ReadS [Type]
readList :: ReadS [Type]
$creadPrec :: ReadPrec Type
readPrec :: ReadPrec Type
$creadListPrec :: ReadPrec [Type]
readListPrec :: ReadPrec [Type]
Read, Int -> Type -> ShowS
[Type] -> ShowS
Type -> String
(Int -> Type -> ShowS)
-> (Type -> String) -> ([Type] -> ShowS) -> Show Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Type -> ShowS
showsPrec :: Int -> Type -> ShowS
$cshow :: Type -> String
show :: Type -> String
$cshowList :: [Type] -> ShowS
showList :: [Type] -> ShowS
Show)
_Type :: Name
_Type = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Type")
_Type_application :: Name
_Type_application = (String -> Name
Core.Name String
"application")
_Type_ctx :: Name
_Type_ctx = (String -> Name
Core.Name String
"ctx")
_Type_function :: Name
_Type_function = (String -> Name
Core.Name String
"function")
_Type_infix :: Name
_Type_infix = (String -> Name
Core.Name String
"infix")
_Type_list :: Name
_Type_list = (String -> Name
Core.Name String
"list")
_Type_parens :: Name
_Type_parens = (String -> Name
Core.Name String
"parens")
_Type_tuple :: Name
_Type_tuple = (String -> Name
Core.Name String
"tuple")
_Type_variable :: Name
_Type_variable = (String -> Name
Core.Name String
"variable")
data Type_Application =
Type_Application {
Type_Application -> Type
type_ApplicationContext :: Type,
Type_Application -> Type
type_ApplicationArgument :: Type}
deriving (Type_Application -> Type_Application -> Bool
(Type_Application -> Type_Application -> Bool)
-> (Type_Application -> Type_Application -> Bool)
-> Eq Type_Application
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type_Application -> Type_Application -> Bool
== :: Type_Application -> Type_Application -> Bool
$c/= :: Type_Application -> Type_Application -> Bool
/= :: Type_Application -> Type_Application -> Bool
Eq, Eq Type_Application
Eq Type_Application =>
(Type_Application -> Type_Application -> Ordering)
-> (Type_Application -> Type_Application -> Bool)
-> (Type_Application -> Type_Application -> Bool)
-> (Type_Application -> Type_Application -> Bool)
-> (Type_Application -> Type_Application -> Bool)
-> (Type_Application -> Type_Application -> Type_Application)
-> (Type_Application -> Type_Application -> Type_Application)
-> Ord Type_Application
Type_Application -> Type_Application -> Bool
Type_Application -> Type_Application -> Ordering
Type_Application -> Type_Application -> Type_Application
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Type_Application -> Type_Application -> Ordering
compare :: Type_Application -> Type_Application -> Ordering
$c< :: Type_Application -> Type_Application -> Bool
< :: Type_Application -> Type_Application -> Bool
$c<= :: Type_Application -> Type_Application -> Bool
<= :: Type_Application -> Type_Application -> Bool
$c> :: Type_Application -> Type_Application -> Bool
> :: Type_Application -> Type_Application -> Bool
$c>= :: Type_Application -> Type_Application -> Bool
>= :: Type_Application -> Type_Application -> Bool
$cmax :: Type_Application -> Type_Application -> Type_Application
max :: Type_Application -> Type_Application -> Type_Application
$cmin :: Type_Application -> Type_Application -> Type_Application
min :: Type_Application -> Type_Application -> Type_Application
Ord, ReadPrec [Type_Application]
ReadPrec Type_Application
Int -> ReadS Type_Application
ReadS [Type_Application]
(Int -> ReadS Type_Application)
-> ReadS [Type_Application]
-> ReadPrec Type_Application
-> ReadPrec [Type_Application]
-> Read Type_Application
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Type_Application
readsPrec :: Int -> ReadS Type_Application
$creadList :: ReadS [Type_Application]
readList :: ReadS [Type_Application]
$creadPrec :: ReadPrec Type_Application
readPrec :: ReadPrec Type_Application
$creadListPrec :: ReadPrec [Type_Application]
readListPrec :: ReadPrec [Type_Application]
Read, Int -> Type_Application -> ShowS
[Type_Application] -> ShowS
Type_Application -> String
(Int -> Type_Application -> ShowS)
-> (Type_Application -> String)
-> ([Type_Application] -> ShowS)
-> Show Type_Application
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Type_Application -> ShowS
showsPrec :: Int -> Type_Application -> ShowS
$cshow :: Type_Application -> String
show :: Type_Application -> String
$cshowList :: [Type_Application] -> ShowS
showList :: [Type_Application] -> ShowS
Show)
_Type_Application :: Name
_Type_Application = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Type.Application")
_Type_Application_context :: Name
_Type_Application_context = (String -> Name
Core.Name String
"context")
_Type_Application_argument :: Name
_Type_Application_argument = (String -> Name
Core.Name String
"argument")
data Type_Context =
Type_Context {
Type_Context -> Assertion
type_ContextCtx :: Assertion,
Type_Context -> Type
type_ContextType :: Type}
deriving (Type_Context -> Type_Context -> Bool
(Type_Context -> Type_Context -> Bool)
-> (Type_Context -> Type_Context -> Bool) -> Eq Type_Context
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type_Context -> Type_Context -> Bool
== :: Type_Context -> Type_Context -> Bool
$c/= :: Type_Context -> Type_Context -> Bool
/= :: Type_Context -> Type_Context -> Bool
Eq, Eq Type_Context
Eq Type_Context =>
(Type_Context -> Type_Context -> Ordering)
-> (Type_Context -> Type_Context -> Bool)
-> (Type_Context -> Type_Context -> Bool)
-> (Type_Context -> Type_Context -> Bool)
-> (Type_Context -> Type_Context -> Bool)
-> (Type_Context -> Type_Context -> Type_Context)
-> (Type_Context -> Type_Context -> Type_Context)
-> Ord Type_Context
Type_Context -> Type_Context -> Bool
Type_Context -> Type_Context -> Ordering
Type_Context -> Type_Context -> Type_Context
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Type_Context -> Type_Context -> Ordering
compare :: Type_Context -> Type_Context -> Ordering
$c< :: Type_Context -> Type_Context -> Bool
< :: Type_Context -> Type_Context -> Bool
$c<= :: Type_Context -> Type_Context -> Bool
<= :: Type_Context -> Type_Context -> Bool
$c> :: Type_Context -> Type_Context -> Bool
> :: Type_Context -> Type_Context -> Bool
$c>= :: Type_Context -> Type_Context -> Bool
>= :: Type_Context -> Type_Context -> Bool
$cmax :: Type_Context -> Type_Context -> Type_Context
max :: Type_Context -> Type_Context -> Type_Context
$cmin :: Type_Context -> Type_Context -> Type_Context
min :: Type_Context -> Type_Context -> Type_Context
Ord, ReadPrec [Type_Context]
ReadPrec Type_Context
Int -> ReadS Type_Context
ReadS [Type_Context]
(Int -> ReadS Type_Context)
-> ReadS [Type_Context]
-> ReadPrec Type_Context
-> ReadPrec [Type_Context]
-> Read Type_Context
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Type_Context
readsPrec :: Int -> ReadS Type_Context
$creadList :: ReadS [Type_Context]
readList :: ReadS [Type_Context]
$creadPrec :: ReadPrec Type_Context
readPrec :: ReadPrec Type_Context
$creadListPrec :: ReadPrec [Type_Context]
readListPrec :: ReadPrec [Type_Context]
Read, Int -> Type_Context -> ShowS
[Type_Context] -> ShowS
Type_Context -> String
(Int -> Type_Context -> ShowS)
-> (Type_Context -> String)
-> ([Type_Context] -> ShowS)
-> Show Type_Context
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Type_Context -> ShowS
showsPrec :: Int -> Type_Context -> ShowS
$cshow :: Type_Context -> String
show :: Type_Context -> String
$cshowList :: [Type_Context] -> ShowS
showList :: [Type_Context] -> ShowS
Show)
_Type_Context :: Name
_Type_Context = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Type.Context")
_Type_Context_ctx :: Name
_Type_Context_ctx = (String -> Name
Core.Name String
"ctx")
_Type_Context_type :: Name
_Type_Context_type = (String -> Name
Core.Name String
"type")
data Type_Function =
Type_Function {
Type_Function -> Type
type_FunctionDomain :: Type,
Type_Function -> Type
type_FunctionCodomain :: Type}
deriving (Type_Function -> Type_Function -> Bool
(Type_Function -> Type_Function -> Bool)
-> (Type_Function -> Type_Function -> Bool) -> Eq Type_Function
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type_Function -> Type_Function -> Bool
== :: Type_Function -> Type_Function -> Bool
$c/= :: Type_Function -> Type_Function -> Bool
/= :: Type_Function -> Type_Function -> Bool
Eq, Eq Type_Function
Eq Type_Function =>
(Type_Function -> Type_Function -> Ordering)
-> (Type_Function -> Type_Function -> Bool)
-> (Type_Function -> Type_Function -> Bool)
-> (Type_Function -> Type_Function -> Bool)
-> (Type_Function -> Type_Function -> Bool)
-> (Type_Function -> Type_Function -> Type_Function)
-> (Type_Function -> Type_Function -> Type_Function)
-> Ord Type_Function
Type_Function -> Type_Function -> Bool
Type_Function -> Type_Function -> Ordering
Type_Function -> Type_Function -> Type_Function
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Type_Function -> Type_Function -> Ordering
compare :: Type_Function -> Type_Function -> Ordering
$c< :: Type_Function -> Type_Function -> Bool
< :: Type_Function -> Type_Function -> Bool
$c<= :: Type_Function -> Type_Function -> Bool
<= :: Type_Function -> Type_Function -> Bool
$c> :: Type_Function -> Type_Function -> Bool
> :: Type_Function -> Type_Function -> Bool
$c>= :: Type_Function -> Type_Function -> Bool
>= :: Type_Function -> Type_Function -> Bool
$cmax :: Type_Function -> Type_Function -> Type_Function
max :: Type_Function -> Type_Function -> Type_Function
$cmin :: Type_Function -> Type_Function -> Type_Function
min :: Type_Function -> Type_Function -> Type_Function
Ord, ReadPrec [Type_Function]
ReadPrec Type_Function
Int -> ReadS Type_Function
ReadS [Type_Function]
(Int -> ReadS Type_Function)
-> ReadS [Type_Function]
-> ReadPrec Type_Function
-> ReadPrec [Type_Function]
-> Read Type_Function
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Type_Function
readsPrec :: Int -> ReadS Type_Function
$creadList :: ReadS [Type_Function]
readList :: ReadS [Type_Function]
$creadPrec :: ReadPrec Type_Function
readPrec :: ReadPrec Type_Function
$creadListPrec :: ReadPrec [Type_Function]
readListPrec :: ReadPrec [Type_Function]
Read, Int -> Type_Function -> ShowS
[Type_Function] -> ShowS
Type_Function -> String
(Int -> Type_Function -> ShowS)
-> (Type_Function -> String)
-> ([Type_Function] -> ShowS)
-> Show Type_Function
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Type_Function -> ShowS
showsPrec :: Int -> Type_Function -> ShowS
$cshow :: Type_Function -> String
show :: Type_Function -> String
$cshowList :: [Type_Function] -> ShowS
showList :: [Type_Function] -> ShowS
Show)
_Type_Function :: Name
_Type_Function = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Type.Function")
_Type_Function_domain :: Name
_Type_Function_domain = (String -> Name
Core.Name String
"domain")
_Type_Function_codomain :: Name
_Type_Function_codomain = (String -> Name
Core.Name String
"codomain")
data Type_Infix =
Type_Infix {
Type_Infix -> Type
type_InfixLhs :: Type,
Type_Infix -> Operator
type_InfixOperator :: Operator,
Type_Infix -> Operator
type_InfixRhs :: Operator}
deriving (Type_Infix -> Type_Infix -> Bool
(Type_Infix -> Type_Infix -> Bool)
-> (Type_Infix -> Type_Infix -> Bool) -> Eq Type_Infix
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type_Infix -> Type_Infix -> Bool
== :: Type_Infix -> Type_Infix -> Bool
$c/= :: Type_Infix -> Type_Infix -> Bool
/= :: Type_Infix -> Type_Infix -> Bool
Eq, Eq Type_Infix
Eq Type_Infix =>
(Type_Infix -> Type_Infix -> Ordering)
-> (Type_Infix -> Type_Infix -> Bool)
-> (Type_Infix -> Type_Infix -> Bool)
-> (Type_Infix -> Type_Infix -> Bool)
-> (Type_Infix -> Type_Infix -> Bool)
-> (Type_Infix -> Type_Infix -> Type_Infix)
-> (Type_Infix -> Type_Infix -> Type_Infix)
-> Ord Type_Infix
Type_Infix -> Type_Infix -> Bool
Type_Infix -> Type_Infix -> Ordering
Type_Infix -> Type_Infix -> Type_Infix
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Type_Infix -> Type_Infix -> Ordering
compare :: Type_Infix -> Type_Infix -> Ordering
$c< :: Type_Infix -> Type_Infix -> Bool
< :: Type_Infix -> Type_Infix -> Bool
$c<= :: Type_Infix -> Type_Infix -> Bool
<= :: Type_Infix -> Type_Infix -> Bool
$c> :: Type_Infix -> Type_Infix -> Bool
> :: Type_Infix -> Type_Infix -> Bool
$c>= :: Type_Infix -> Type_Infix -> Bool
>= :: Type_Infix -> Type_Infix -> Bool
$cmax :: Type_Infix -> Type_Infix -> Type_Infix
max :: Type_Infix -> Type_Infix -> Type_Infix
$cmin :: Type_Infix -> Type_Infix -> Type_Infix
min :: Type_Infix -> Type_Infix -> Type_Infix
Ord, ReadPrec [Type_Infix]
ReadPrec Type_Infix
Int -> ReadS Type_Infix
ReadS [Type_Infix]
(Int -> ReadS Type_Infix)
-> ReadS [Type_Infix]
-> ReadPrec Type_Infix
-> ReadPrec [Type_Infix]
-> Read Type_Infix
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Type_Infix
readsPrec :: Int -> ReadS Type_Infix
$creadList :: ReadS [Type_Infix]
readList :: ReadS [Type_Infix]
$creadPrec :: ReadPrec Type_Infix
readPrec :: ReadPrec Type_Infix
$creadListPrec :: ReadPrec [Type_Infix]
readListPrec :: ReadPrec [Type_Infix]
Read, Int -> Type_Infix -> ShowS
[Type_Infix] -> ShowS
Type_Infix -> String
(Int -> Type_Infix -> ShowS)
-> (Type_Infix -> String)
-> ([Type_Infix] -> ShowS)
-> Show Type_Infix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Type_Infix -> ShowS
showsPrec :: Int -> Type_Infix -> ShowS
$cshow :: Type_Infix -> String
show :: Type_Infix -> String
$cshowList :: [Type_Infix] -> ShowS
showList :: [Type_Infix] -> ShowS
Show)
_Type_Infix :: Name
_Type_Infix = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Type.Infix")
_Type_Infix_lhs :: Name
_Type_Infix_lhs = (String -> Name
Core.Name String
"lhs")
_Type_Infix_operator :: Name
_Type_Infix_operator = (String -> Name
Core.Name String
"operator")
_Type_Infix_rhs :: Name
_Type_Infix_rhs = (String -> Name
Core.Name String
"rhs")
data TypeDeclaration =
TypeDeclaration {
TypeDeclaration -> DeclarationHead
typeDeclarationName :: DeclarationHead,
TypeDeclaration -> Type
typeDeclarationType :: Type}
deriving (TypeDeclaration -> TypeDeclaration -> Bool
(TypeDeclaration -> TypeDeclaration -> Bool)
-> (TypeDeclaration -> TypeDeclaration -> Bool)
-> Eq TypeDeclaration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeDeclaration -> TypeDeclaration -> Bool
== :: TypeDeclaration -> TypeDeclaration -> Bool
$c/= :: TypeDeclaration -> TypeDeclaration -> Bool
/= :: TypeDeclaration -> TypeDeclaration -> Bool
Eq, Eq TypeDeclaration
Eq TypeDeclaration =>
(TypeDeclaration -> TypeDeclaration -> Ordering)
-> (TypeDeclaration -> TypeDeclaration -> Bool)
-> (TypeDeclaration -> TypeDeclaration -> Bool)
-> (TypeDeclaration -> TypeDeclaration -> Bool)
-> (TypeDeclaration -> TypeDeclaration -> Bool)
-> (TypeDeclaration -> TypeDeclaration -> TypeDeclaration)
-> (TypeDeclaration -> TypeDeclaration -> TypeDeclaration)
-> Ord TypeDeclaration
TypeDeclaration -> TypeDeclaration -> Bool
TypeDeclaration -> TypeDeclaration -> Ordering
TypeDeclaration -> TypeDeclaration -> TypeDeclaration
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TypeDeclaration -> TypeDeclaration -> Ordering
compare :: TypeDeclaration -> TypeDeclaration -> Ordering
$c< :: TypeDeclaration -> TypeDeclaration -> Bool
< :: TypeDeclaration -> TypeDeclaration -> Bool
$c<= :: TypeDeclaration -> TypeDeclaration -> Bool
<= :: TypeDeclaration -> TypeDeclaration -> Bool
$c> :: TypeDeclaration -> TypeDeclaration -> Bool
> :: TypeDeclaration -> TypeDeclaration -> Bool
$c>= :: TypeDeclaration -> TypeDeclaration -> Bool
>= :: TypeDeclaration -> TypeDeclaration -> Bool
$cmax :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration
max :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration
$cmin :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration
min :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration
Ord, ReadPrec [TypeDeclaration]
ReadPrec TypeDeclaration
Int -> ReadS TypeDeclaration
ReadS [TypeDeclaration]
(Int -> ReadS TypeDeclaration)
-> ReadS [TypeDeclaration]
-> ReadPrec TypeDeclaration
-> ReadPrec [TypeDeclaration]
-> Read TypeDeclaration
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeDeclaration
readsPrec :: Int -> ReadS TypeDeclaration
$creadList :: ReadS [TypeDeclaration]
readList :: ReadS [TypeDeclaration]
$creadPrec :: ReadPrec TypeDeclaration
readPrec :: ReadPrec TypeDeclaration
$creadListPrec :: ReadPrec [TypeDeclaration]
readListPrec :: ReadPrec [TypeDeclaration]
Read, Int -> TypeDeclaration -> ShowS
[TypeDeclaration] -> ShowS
TypeDeclaration -> String
(Int -> TypeDeclaration -> ShowS)
-> (TypeDeclaration -> String)
-> ([TypeDeclaration] -> ShowS)
-> Show TypeDeclaration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TypeDeclaration -> ShowS
showsPrec :: Int -> TypeDeclaration -> ShowS
$cshow :: TypeDeclaration -> String
show :: TypeDeclaration -> String
$cshowList :: [TypeDeclaration] -> ShowS
showList :: [TypeDeclaration] -> ShowS
Show)
_TypeDeclaration :: Name
_TypeDeclaration = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.TypeDeclaration")
_TypeDeclaration_name :: Name
_TypeDeclaration_name = (String -> Name
Core.Name String
"name")
_TypeDeclaration_type :: Name
_TypeDeclaration_type = (String -> Name
Core.Name String
"type")
data TypeSignature =
TypeSignature {
TypeSignature -> Name
typeSignatureName :: Name,
TypeSignature -> Type
typeSignatureType :: Type}
deriving (TypeSignature -> TypeSignature -> Bool
(TypeSignature -> TypeSignature -> Bool)
-> (TypeSignature -> TypeSignature -> Bool) -> Eq TypeSignature
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeSignature -> TypeSignature -> Bool
== :: TypeSignature -> TypeSignature -> Bool
$c/= :: TypeSignature -> TypeSignature -> Bool
/= :: TypeSignature -> TypeSignature -> Bool
Eq, Eq TypeSignature
Eq TypeSignature =>
(TypeSignature -> TypeSignature -> Ordering)
-> (TypeSignature -> TypeSignature -> Bool)
-> (TypeSignature -> TypeSignature -> Bool)
-> (TypeSignature -> TypeSignature -> Bool)
-> (TypeSignature -> TypeSignature -> Bool)
-> (TypeSignature -> TypeSignature -> TypeSignature)
-> (TypeSignature -> TypeSignature -> TypeSignature)
-> Ord TypeSignature
TypeSignature -> TypeSignature -> Bool
TypeSignature -> TypeSignature -> Ordering
TypeSignature -> TypeSignature -> TypeSignature
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TypeSignature -> TypeSignature -> Ordering
compare :: TypeSignature -> TypeSignature -> Ordering
$c< :: TypeSignature -> TypeSignature -> Bool
< :: TypeSignature -> TypeSignature -> Bool
$c<= :: TypeSignature -> TypeSignature -> Bool
<= :: TypeSignature -> TypeSignature -> Bool
$c> :: TypeSignature -> TypeSignature -> Bool
> :: TypeSignature -> TypeSignature -> Bool
$c>= :: TypeSignature -> TypeSignature -> Bool
>= :: TypeSignature -> TypeSignature -> Bool
$cmax :: TypeSignature -> TypeSignature -> TypeSignature
max :: TypeSignature -> TypeSignature -> TypeSignature
$cmin :: TypeSignature -> TypeSignature -> TypeSignature
min :: TypeSignature -> TypeSignature -> TypeSignature
Ord, ReadPrec [TypeSignature]
ReadPrec TypeSignature
Int -> ReadS TypeSignature
ReadS [TypeSignature]
(Int -> ReadS TypeSignature)
-> ReadS [TypeSignature]
-> ReadPrec TypeSignature
-> ReadPrec [TypeSignature]
-> Read TypeSignature
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeSignature
readsPrec :: Int -> ReadS TypeSignature
$creadList :: ReadS [TypeSignature]
readList :: ReadS [TypeSignature]
$creadPrec :: ReadPrec TypeSignature
readPrec :: ReadPrec TypeSignature
$creadListPrec :: ReadPrec [TypeSignature]
readListPrec :: ReadPrec [TypeSignature]
Read, Int -> TypeSignature -> ShowS
[TypeSignature] -> ShowS
TypeSignature -> String
(Int -> TypeSignature -> ShowS)
-> (TypeSignature -> String)
-> ([TypeSignature] -> ShowS)
-> Show TypeSignature
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TypeSignature -> ShowS
showsPrec :: Int -> TypeSignature -> ShowS
$cshow :: TypeSignature -> String
show :: TypeSignature -> String
$cshowList :: [TypeSignature] -> ShowS
showList :: [TypeSignature] -> ShowS
Show)
_TypeSignature :: Name
_TypeSignature = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.TypeSignature")
_TypeSignature_name :: Name
_TypeSignature_name = (String -> Name
Core.Name String
"name")
_TypeSignature_type :: Name
_TypeSignature_type = (String -> Name
Core.Name String
"type")
data TypedBinding =
TypedBinding {
TypedBinding -> TypeSignature
typedBindingTypeSignature :: TypeSignature,
TypedBinding -> ValueBinding
typedBindingValueBinding :: ValueBinding}
deriving (TypedBinding -> TypedBinding -> Bool
(TypedBinding -> TypedBinding -> Bool)
-> (TypedBinding -> TypedBinding -> Bool) -> Eq TypedBinding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypedBinding -> TypedBinding -> Bool
== :: TypedBinding -> TypedBinding -> Bool
$c/= :: TypedBinding -> TypedBinding -> Bool
/= :: TypedBinding -> TypedBinding -> Bool
Eq, Eq TypedBinding
Eq TypedBinding =>
(TypedBinding -> TypedBinding -> Ordering)
-> (TypedBinding -> TypedBinding -> Bool)
-> (TypedBinding -> TypedBinding -> Bool)
-> (TypedBinding -> TypedBinding -> Bool)
-> (TypedBinding -> TypedBinding -> Bool)
-> (TypedBinding -> TypedBinding -> TypedBinding)
-> (TypedBinding -> TypedBinding -> TypedBinding)
-> Ord TypedBinding
TypedBinding -> TypedBinding -> Bool
TypedBinding -> TypedBinding -> Ordering
TypedBinding -> TypedBinding -> TypedBinding
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TypedBinding -> TypedBinding -> Ordering
compare :: TypedBinding -> TypedBinding -> Ordering
$c< :: TypedBinding -> TypedBinding -> Bool
< :: TypedBinding -> TypedBinding -> Bool
$c<= :: TypedBinding -> TypedBinding -> Bool
<= :: TypedBinding -> TypedBinding -> Bool
$c> :: TypedBinding -> TypedBinding -> Bool
> :: TypedBinding -> TypedBinding -> Bool
$c>= :: TypedBinding -> TypedBinding -> Bool
>= :: TypedBinding -> TypedBinding -> Bool
$cmax :: TypedBinding -> TypedBinding -> TypedBinding
max :: TypedBinding -> TypedBinding -> TypedBinding
$cmin :: TypedBinding -> TypedBinding -> TypedBinding
min :: TypedBinding -> TypedBinding -> TypedBinding
Ord, ReadPrec [TypedBinding]
ReadPrec TypedBinding
Int -> ReadS TypedBinding
ReadS [TypedBinding]
(Int -> ReadS TypedBinding)
-> ReadS [TypedBinding]
-> ReadPrec TypedBinding
-> ReadPrec [TypedBinding]
-> Read TypedBinding
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypedBinding
readsPrec :: Int -> ReadS TypedBinding
$creadList :: ReadS [TypedBinding]
readList :: ReadS [TypedBinding]
$creadPrec :: ReadPrec TypedBinding
readPrec :: ReadPrec TypedBinding
$creadListPrec :: ReadPrec [TypedBinding]
readListPrec :: ReadPrec [TypedBinding]
Read, Int -> TypedBinding -> ShowS
[TypedBinding] -> ShowS
TypedBinding -> String
(Int -> TypedBinding -> ShowS)
-> (TypedBinding -> String)
-> ([TypedBinding] -> ShowS)
-> Show TypedBinding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TypedBinding -> ShowS
showsPrec :: Int -> TypedBinding -> ShowS
$cshow :: TypedBinding -> String
show :: TypedBinding -> String
$cshowList :: [TypedBinding] -> ShowS
showList :: [TypedBinding] -> ShowS
Show)
_TypedBinding :: Name
_TypedBinding = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.TypedBinding")
_TypedBinding_typeSignature :: Name
_TypedBinding_typeSignature = (String -> Name
Core.Name String
"typeSignature")
_TypedBinding_valueBinding :: Name
_TypedBinding_valueBinding = (String -> Name
Core.Name String
"valueBinding")
data ValueBinding =
ValueBindingSimple ValueBinding_Simple
deriving (ValueBinding -> ValueBinding -> Bool
(ValueBinding -> ValueBinding -> Bool)
-> (ValueBinding -> ValueBinding -> Bool) -> Eq ValueBinding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ValueBinding -> ValueBinding -> Bool
== :: ValueBinding -> ValueBinding -> Bool
$c/= :: ValueBinding -> ValueBinding -> Bool
/= :: ValueBinding -> ValueBinding -> Bool
Eq, Eq ValueBinding
Eq ValueBinding =>
(ValueBinding -> ValueBinding -> Ordering)
-> (ValueBinding -> ValueBinding -> Bool)
-> (ValueBinding -> ValueBinding -> Bool)
-> (ValueBinding -> ValueBinding -> Bool)
-> (ValueBinding -> ValueBinding -> Bool)
-> (ValueBinding -> ValueBinding -> ValueBinding)
-> (ValueBinding -> ValueBinding -> ValueBinding)
-> Ord ValueBinding
ValueBinding -> ValueBinding -> Bool
ValueBinding -> ValueBinding -> Ordering
ValueBinding -> ValueBinding -> ValueBinding
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ValueBinding -> ValueBinding -> Ordering
compare :: ValueBinding -> ValueBinding -> Ordering
$c< :: ValueBinding -> ValueBinding -> Bool
< :: ValueBinding -> ValueBinding -> Bool
$c<= :: ValueBinding -> ValueBinding -> Bool
<= :: ValueBinding -> ValueBinding -> Bool
$c> :: ValueBinding -> ValueBinding -> Bool
> :: ValueBinding -> ValueBinding -> Bool
$c>= :: ValueBinding -> ValueBinding -> Bool
>= :: ValueBinding -> ValueBinding -> Bool
$cmax :: ValueBinding -> ValueBinding -> ValueBinding
max :: ValueBinding -> ValueBinding -> ValueBinding
$cmin :: ValueBinding -> ValueBinding -> ValueBinding
min :: ValueBinding -> ValueBinding -> ValueBinding
Ord, ReadPrec [ValueBinding]
ReadPrec ValueBinding
Int -> ReadS ValueBinding
ReadS [ValueBinding]
(Int -> ReadS ValueBinding)
-> ReadS [ValueBinding]
-> ReadPrec ValueBinding
-> ReadPrec [ValueBinding]
-> Read ValueBinding
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ValueBinding
readsPrec :: Int -> ReadS ValueBinding
$creadList :: ReadS [ValueBinding]
readList :: ReadS [ValueBinding]
$creadPrec :: ReadPrec ValueBinding
readPrec :: ReadPrec ValueBinding
$creadListPrec :: ReadPrec [ValueBinding]
readListPrec :: ReadPrec [ValueBinding]
Read, Int -> ValueBinding -> ShowS
[ValueBinding] -> ShowS
ValueBinding -> String
(Int -> ValueBinding -> ShowS)
-> (ValueBinding -> String)
-> ([ValueBinding] -> ShowS)
-> Show ValueBinding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ValueBinding -> ShowS
showsPrec :: Int -> ValueBinding -> ShowS
$cshow :: ValueBinding -> String
show :: ValueBinding -> String
$cshowList :: [ValueBinding] -> ShowS
showList :: [ValueBinding] -> ShowS
Show)
_ValueBinding :: Name
_ValueBinding = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.ValueBinding")
_ValueBinding_simple :: Name
_ValueBinding_simple = (String -> Name
Core.Name String
"simple")
data ValueBinding_Simple =
ValueBinding_Simple {
ValueBinding_Simple -> Pattern
valueBinding_SimplePattern :: Pattern,
ValueBinding_Simple -> RightHandSide
valueBinding_SimpleRhs :: RightHandSide,
ValueBinding_Simple -> Maybe LocalBindings
valueBinding_SimpleLocalBindings :: (Maybe LocalBindings)}
deriving (ValueBinding_Simple -> ValueBinding_Simple -> Bool
(ValueBinding_Simple -> ValueBinding_Simple -> Bool)
-> (ValueBinding_Simple -> ValueBinding_Simple -> Bool)
-> Eq ValueBinding_Simple
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
== :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
$c/= :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
/= :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
Eq, Eq ValueBinding_Simple
Eq ValueBinding_Simple =>
(ValueBinding_Simple -> ValueBinding_Simple -> Ordering)
-> (ValueBinding_Simple -> ValueBinding_Simple -> Bool)
-> (ValueBinding_Simple -> ValueBinding_Simple -> Bool)
-> (ValueBinding_Simple -> ValueBinding_Simple -> Bool)
-> (ValueBinding_Simple -> ValueBinding_Simple -> Bool)
-> (ValueBinding_Simple
-> ValueBinding_Simple -> ValueBinding_Simple)
-> (ValueBinding_Simple
-> ValueBinding_Simple -> ValueBinding_Simple)
-> Ord ValueBinding_Simple
ValueBinding_Simple -> ValueBinding_Simple -> Bool
ValueBinding_Simple -> ValueBinding_Simple -> Ordering
ValueBinding_Simple -> ValueBinding_Simple -> ValueBinding_Simple
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ValueBinding_Simple -> ValueBinding_Simple -> Ordering
compare :: ValueBinding_Simple -> ValueBinding_Simple -> Ordering
$c< :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
< :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
$c<= :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
<= :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
$c> :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
> :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
$c>= :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
>= :: ValueBinding_Simple -> ValueBinding_Simple -> Bool
$cmax :: ValueBinding_Simple -> ValueBinding_Simple -> ValueBinding_Simple
max :: ValueBinding_Simple -> ValueBinding_Simple -> ValueBinding_Simple
$cmin :: ValueBinding_Simple -> ValueBinding_Simple -> ValueBinding_Simple
min :: ValueBinding_Simple -> ValueBinding_Simple -> ValueBinding_Simple
Ord, ReadPrec [ValueBinding_Simple]
ReadPrec ValueBinding_Simple
Int -> ReadS ValueBinding_Simple
ReadS [ValueBinding_Simple]
(Int -> ReadS ValueBinding_Simple)
-> ReadS [ValueBinding_Simple]
-> ReadPrec ValueBinding_Simple
-> ReadPrec [ValueBinding_Simple]
-> Read ValueBinding_Simple
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ValueBinding_Simple
readsPrec :: Int -> ReadS ValueBinding_Simple
$creadList :: ReadS [ValueBinding_Simple]
readList :: ReadS [ValueBinding_Simple]
$creadPrec :: ReadPrec ValueBinding_Simple
readPrec :: ReadPrec ValueBinding_Simple
$creadListPrec :: ReadPrec [ValueBinding_Simple]
readListPrec :: ReadPrec [ValueBinding_Simple]
Read, Int -> ValueBinding_Simple -> ShowS
[ValueBinding_Simple] -> ShowS
ValueBinding_Simple -> String
(Int -> ValueBinding_Simple -> ShowS)
-> (ValueBinding_Simple -> String)
-> ([ValueBinding_Simple] -> ShowS)
-> Show ValueBinding_Simple
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ValueBinding_Simple -> ShowS
showsPrec :: Int -> ValueBinding_Simple -> ShowS
$cshow :: ValueBinding_Simple -> String
show :: ValueBinding_Simple -> String
$cshowList :: [ValueBinding_Simple] -> ShowS
showList :: [ValueBinding_Simple] -> ShowS
Show)
_ValueBinding_Simple :: Name
_ValueBinding_Simple = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.ValueBinding.Simple")
_ValueBinding_Simple_pattern :: Name
_ValueBinding_Simple_pattern = (String -> Name
Core.Name String
"pattern")
_ValueBinding_Simple_rhs :: Name
_ValueBinding_Simple_rhs = (String -> Name
Core.Name String
"rhs")
_ValueBinding_Simple_localBindings :: Name
_ValueBinding_Simple_localBindings = (String -> Name
Core.Name String
"localBindings")
newtype Variable =
Variable {
Variable -> Name
unVariable :: Name}
deriving (Variable -> Variable -> Bool
(Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool) -> Eq Variable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Variable -> Variable -> Bool
== :: Variable -> Variable -> Bool
$c/= :: Variable -> Variable -> Bool
/= :: Variable -> Variable -> Bool
Eq, Eq Variable
Eq Variable =>
(Variable -> Variable -> Ordering)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Variable)
-> (Variable -> Variable -> Variable)
-> Ord Variable
Variable -> Variable -> Bool
Variable -> Variable -> Ordering
Variable -> Variable -> Variable
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Variable -> Variable -> Ordering
compare :: Variable -> Variable -> Ordering
$c< :: Variable -> Variable -> Bool
< :: Variable -> Variable -> Bool
$c<= :: Variable -> Variable -> Bool
<= :: Variable -> Variable -> Bool
$c> :: Variable -> Variable -> Bool
> :: Variable -> Variable -> Bool
$c>= :: Variable -> Variable -> Bool
>= :: Variable -> Variable -> Bool
$cmax :: Variable -> Variable -> Variable
max :: Variable -> Variable -> Variable
$cmin :: Variable -> Variable -> Variable
min :: Variable -> Variable -> Variable
Ord, ReadPrec [Variable]
ReadPrec Variable
Int -> ReadS Variable
ReadS [Variable]
(Int -> ReadS Variable)
-> ReadS [Variable]
-> ReadPrec Variable
-> ReadPrec [Variable]
-> Read Variable
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Variable
readsPrec :: Int -> ReadS Variable
$creadList :: ReadS [Variable]
readList :: ReadS [Variable]
$creadPrec :: ReadPrec Variable
readPrec :: ReadPrec Variable
$creadListPrec :: ReadPrec [Variable]
readListPrec :: ReadPrec [Variable]
Read, Int -> Variable -> ShowS
[Variable] -> ShowS
Variable -> String
(Int -> Variable -> ShowS)
-> (Variable -> String) -> ([Variable] -> ShowS) -> Show Variable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Variable -> ShowS
showsPrec :: Int -> Variable -> ShowS
$cshow :: Variable -> String
show :: Variable -> String
$cshowList :: [Variable] -> ShowS
showList :: [Variable] -> ShowS
Show)
_Variable :: Name
_Variable = (String -> Name
Core.Name String
"hydra/langs/haskell/ast.Variable")