{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE FlexibleInstances #-}
module Cryptol.Parser.AST
(
Ident, mkIdent, mkInfix, isInfixIdent, nullIdent, identText
, ModName, modRange
, PName(..), getModName, getIdent, mkUnqual, mkQual
, Named(..)
, Pass(..)
, Assoc(..)
, Schema(..)
, TParam(..)
, Kind(..)
, Type(..)
, Prop(..)
, tsName
, psName
, tsFixity
, psFixity
, Module
, ModuleG(..)
, mDecls
, mImports
, mModParams
, mIsFunctor
, isParamDecl
, ModuleDefinition(..)
, ModuleInstanceArgs(..)
, ModuleInstanceNamedArg(..)
, ModuleInstanceArg(..)
, ModuleInstance
, emptyModuleInstance
, Program(..)
, TopDecl(..)
, Decl(..)
, Fixity(..), defaultFixity
, FixityCmp(..), compareFixity
, TySyn(..)
, PropSyn(..)
, Bind(..), bindParams, bindHeaderLoc
, BindParams(..), dropParams, noParams
, BindDef(..), LBindDef
, BindImpl(..), bindImpl, exprDef
, Pragma(..)
, ExportType(..)
, TopLevel(..)
, Import, ImportG(..), ImportSpec(..), ImpName(..), impNameModPath
, Newtype(..)
, EnumDecl(..), EnumCon(..)
, PrimType(..)
, ParameterType(..)
, ParameterFun(..)
, ParameterConstraint(..)
, NestedModule(..)
, Signature(..)
, SigDecl(..)
, ModParam(..)
, ParamDecl(..)
, PropGuardCase(..)
, ReplInput(..)
, Expr(..)
, Literal(..), NumInfo(..), FracInfo(..)
, Match(..)
, Pattern(..)
, Selector(..)
, CaseAlt(..)
, TypeInst(..)
, UpdField(..)
, UpdHow(..)
, FunDesc(..)
, emptyFunDesc
, PrefixOp(..)
, prefixFixity
, asEApps
, Located(..)
, LPName, LString, LIdent
, NoPos(..)
, cppKind, ppSelector
) where
import Cryptol.ModuleSystem.Name (Name, nameModPath, nameIdent)
import Cryptol.ModuleSystem.NamingEnv.Types
import Cryptol.Parser.Name
import Cryptol.Parser.Position
import Cryptol.Parser.Selector
import Cryptol.Utils.Fixity
import Cryptol.Utils.Ident
import Cryptol.Utils.RecordMap
import Cryptol.Utils.PP
import Data.Map(Map)
import qualified Data.Map as Map
import Data.List(intersperse)
import Data.Bits(shiftR)
import Data.Maybe (catMaybes,mapMaybe)
import Data.Ratio(numerator,denominator)
import Data.Text (Text)
import Numeric(showIntAtBase,showFloat,showHFloat)
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
type LPName = Located PName
type LIdent = Located Ident
type LString = Located String
type Rec e = RecordMap Ident (Range, e)
newtype Program name = Program [TopDecl name]
deriving (Int -> Program name -> ShowS
[Program name] -> ShowS
Program name -> String
(Int -> Program name -> ShowS)
-> (Program name -> String)
-> ([Program name] -> ShowS)
-> Show (Program name)
forall name. Show name => Int -> Program name -> ShowS
forall name. Show name => [Program name] -> ShowS
forall name. Show name => Program name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> Program name -> ShowS
showsPrec :: Int -> Program name -> ShowS
$cshow :: forall name. Show name => Program name -> String
show :: Program name -> String
$cshowList :: forall name. Show name => [Program name] -> ShowS
showList :: [Program name] -> ShowS
Show)
data ModuleG mname name = Module
{ forall mname name. ModuleG mname name -> Located mname
mName :: Located mname
, forall mname name. ModuleG mname name -> ModuleDefinition name
mDef :: ModuleDefinition name
, forall mname name. ModuleG mname name -> NamingEnv
mInScope :: NamingEnv
, forall mname name. ModuleG mname name -> Maybe (Located Text)
mDocTop :: Maybe (Located Text)
} deriving (Int -> ModuleG mname name -> ShowS
[ModuleG mname name] -> ShowS
ModuleG mname name -> String
(Int -> ModuleG mname name -> ShowS)
-> (ModuleG mname name -> String)
-> ([ModuleG mname name] -> ShowS)
-> Show (ModuleG mname name)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall mname name.
(Show mname, Show name) =>
Int -> ModuleG mname name -> ShowS
forall mname name.
(Show mname, Show name) =>
[ModuleG mname name] -> ShowS
forall mname name.
(Show mname, Show name) =>
ModuleG mname name -> String
$cshowsPrec :: forall mname name.
(Show mname, Show name) =>
Int -> ModuleG mname name -> ShowS
showsPrec :: Int -> ModuleG mname name -> ShowS
$cshow :: forall mname name.
(Show mname, Show name) =>
ModuleG mname name -> String
show :: ModuleG mname name -> String
$cshowList :: forall mname name.
(Show mname, Show name) =>
[ModuleG mname name] -> ShowS
showList :: [ModuleG mname name] -> ShowS
Show, (forall x. ModuleG mname name -> Rep (ModuleG mname name) x)
-> (forall x. Rep (ModuleG mname name) x -> ModuleG mname name)
-> Generic (ModuleG mname name)
forall x. Rep (ModuleG mname name) x -> ModuleG mname name
forall x. ModuleG mname name -> Rep (ModuleG mname name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall mname name x.
Rep (ModuleG mname name) x -> ModuleG mname name
forall mname name x.
ModuleG mname name -> Rep (ModuleG mname name) x
$cfrom :: forall mname name x.
ModuleG mname name -> Rep (ModuleG mname name) x
from :: forall x. ModuleG mname name -> Rep (ModuleG mname name) x
$cto :: forall mname name x.
Rep (ModuleG mname name) x -> ModuleG mname name
to :: forall x. Rep (ModuleG mname name) x -> ModuleG mname name
Generic, ModuleG mname name -> ()
(ModuleG mname name -> ()) -> NFData (ModuleG mname name)
forall a. (a -> ()) -> NFData a
forall mname name.
(NFData mname, NFData name) =>
ModuleG mname name -> ()
$crnf :: forall mname name.
(NFData mname, NFData name) =>
ModuleG mname name -> ()
rnf :: ModuleG mname name -> ()
NFData)
data ModuleDefinition name =
NormalModule [TopDecl name]
| FunctorInstance (Located (ImpName name))
(ModuleInstanceArgs name)
(ModuleInstance name)
| InterfaceModule (Signature name)
deriving (Int -> ModuleDefinition name -> ShowS
[ModuleDefinition name] -> ShowS
ModuleDefinition name -> String
(Int -> ModuleDefinition name -> ShowS)
-> (ModuleDefinition name -> String)
-> ([ModuleDefinition name] -> ShowS)
-> Show (ModuleDefinition name)
forall name. Show name => Int -> ModuleDefinition name -> ShowS
forall name. Show name => [ModuleDefinition name] -> ShowS
forall name. Show name => ModuleDefinition name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> ModuleDefinition name -> ShowS
showsPrec :: Int -> ModuleDefinition name -> ShowS
$cshow :: forall name. Show name => ModuleDefinition name -> String
show :: ModuleDefinition name -> String
$cshowList :: forall name. Show name => [ModuleDefinition name] -> ShowS
showList :: [ModuleDefinition name] -> ShowS
Show, (forall x. ModuleDefinition name -> Rep (ModuleDefinition name) x)
-> (forall x.
Rep (ModuleDefinition name) x -> ModuleDefinition name)
-> Generic (ModuleDefinition name)
forall x. Rep (ModuleDefinition name) x -> ModuleDefinition name
forall x. ModuleDefinition name -> Rep (ModuleDefinition name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x.
Rep (ModuleDefinition name) x -> ModuleDefinition name
forall name x.
ModuleDefinition name -> Rep (ModuleDefinition name) x
$cfrom :: forall name x.
ModuleDefinition name -> Rep (ModuleDefinition name) x
from :: forall x. ModuleDefinition name -> Rep (ModuleDefinition name) x
$cto :: forall name x.
Rep (ModuleDefinition name) x -> ModuleDefinition name
to :: forall x. Rep (ModuleDefinition name) x -> ModuleDefinition name
Generic, ModuleDefinition name -> ()
(ModuleDefinition name -> ()) -> NFData (ModuleDefinition name)
forall name. NFData name => ModuleDefinition name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => ModuleDefinition name -> ()
rnf :: ModuleDefinition name -> ()
NFData)
type ModuleInstance name = Map name name
emptyModuleInstance :: Ord name => ModuleInstance name
emptyModuleInstance :: forall name. Ord name => ModuleInstance name
emptyModuleInstance = ModuleInstance name
forall a. Monoid a => a
mempty
mDecls :: ModuleG mname name -> [TopDecl name]
mDecls :: forall mname name. ModuleG mname name -> [TopDecl name]
mDecls ModuleG mname name
m =
case ModuleG mname name -> ModuleDefinition name
forall mname name. ModuleG mname name -> ModuleDefinition name
mDef ModuleG mname name
m of
NormalModule [TopDecl name]
ds -> [TopDecl name]
ds
FunctorInstance Located (ImpName name)
_ ModuleInstanceArgs name
_ ModuleInstance name
_ -> []
InterfaceModule {} -> []
mImports :: ModuleG mname name -> [ Located Import ]
mImports :: forall mname name. ModuleG mname name -> [Located Import]
mImports ModuleG mname name
m =
case ModuleG mname name -> ModuleDefinition name
forall mname name. ModuleG mname name -> ModuleDefinition name
mDef ModuleG mname name
m of
NormalModule [TopDecl name]
ds -> (Located (ImportG (ImpName name)) -> Maybe (Located Import))
-> [Located (ImportG (ImpName name))] -> [Located Import]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Located (ImportG (ImpName name)) -> Maybe (Located Import)
forall {name}.
Located (ImportG (ImpName name)) -> Maybe (Located Import)
topImp [ Located (ImportG (ImpName name))
li | DImport Located (ImportG (ImpName name))
li <- [TopDecl name]
ds ]
FunctorInstance {} -> []
InterfaceModule Signature name
sig -> (Located (ImportG (ImpName name)) -> Maybe (Located Import))
-> [Located (ImportG (ImpName name))] -> [Located Import]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Located (ImportG (ImpName name)) -> Maybe (Located Import)
forall {name}.
Located (ImportG (ImpName name)) -> Maybe (Located Import)
topImp (Signature name -> [Located (ImportG (ImpName name))]
forall name. Signature name -> [Located (ImportG (ImpName name))]
sigImports Signature name
sig)
where
topImp :: Located (ImportG (ImpName name)) -> Maybe (Located Import)
topImp Located (ImportG (ImpName name))
li = case ImportG (ImpName name) -> ImpName name
forall mname. ImportG mname -> mname
iModule ImportG (ImpName name)
i of
ImpTop ModName
n -> Located Import -> Maybe (Located Import)
forall a. a -> Maybe a
Just Located (ImportG (ImpName name))
li { thing = i { iModule = n } }
ImpName name
_ -> Maybe (Located Import)
forall a. Maybe a
Nothing
where i :: ImportG (ImpName name)
i = Located (ImportG (ImpName name)) -> ImportG (ImpName name)
forall a. Located a -> a
thing Located (ImportG (ImpName name))
li
mModParams :: ModuleG mname name -> [ ModParam name ]
mModParams :: forall mname name. ModuleG mname name -> [ModParam name]
mModParams ModuleG mname name
m = [ ModParam name
p | DModParam ModParam name
p <- ModuleG mname name -> [TopDecl name]
forall mname name. ModuleG mname name -> [TopDecl name]
mDecls ModuleG mname name
m ]
mIsFunctor :: ModuleG mname nmae -> Bool
mIsFunctor :: forall mname nmae. ModuleG mname nmae -> Bool
mIsFunctor ModuleG mname nmae
m = (TopDecl nmae -> Bool) -> [TopDecl nmae] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any TopDecl nmae -> Bool
forall a. TopDecl a -> Bool
isParamDecl (ModuleG mname nmae -> [TopDecl nmae]
forall mname name. ModuleG mname name -> [TopDecl name]
mDecls ModuleG mname nmae
m)
isParamDecl :: TopDecl a -> Bool
isParamDecl :: forall a. TopDecl a -> Bool
isParamDecl TopDecl a
d =
case TopDecl a
d of
DModParam {} -> Bool
True
DParamDecl {} -> Bool
True
TopDecl a
_ -> Bool
False
type Module = ModuleG ModName
newtype NestedModule name = NestedModule (ModuleG name name)
deriving (Int -> NestedModule name -> ShowS
[NestedModule name] -> ShowS
NestedModule name -> String
(Int -> NestedModule name -> ShowS)
-> (NestedModule name -> String)
-> ([NestedModule name] -> ShowS)
-> Show (NestedModule name)
forall name. Show name => Int -> NestedModule name -> ShowS
forall name. Show name => [NestedModule name] -> ShowS
forall name. Show name => NestedModule name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> NestedModule name -> ShowS
showsPrec :: Int -> NestedModule name -> ShowS
$cshow :: forall name. Show name => NestedModule name -> String
show :: NestedModule name -> String
$cshowList :: forall name. Show name => [NestedModule name] -> ShowS
showList :: [NestedModule name] -> ShowS
Show,(forall x. NestedModule name -> Rep (NestedModule name) x)
-> (forall x. Rep (NestedModule name) x -> NestedModule name)
-> Generic (NestedModule name)
forall x. Rep (NestedModule name) x -> NestedModule name
forall x. NestedModule name -> Rep (NestedModule name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (NestedModule name) x -> NestedModule name
forall name x. NestedModule name -> Rep (NestedModule name) x
$cfrom :: forall name x. NestedModule name -> Rep (NestedModule name) x
from :: forall x. NestedModule name -> Rep (NestedModule name) x
$cto :: forall name x. Rep (NestedModule name) x -> NestedModule name
to :: forall x. Rep (NestedModule name) x -> NestedModule name
Generic,NestedModule name -> ()
(NestedModule name -> ()) -> NFData (NestedModule name)
forall name. NFData name => NestedModule name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => NestedModule name -> ()
rnf :: NestedModule name -> ()
NFData)
modRange :: Module name -> Range
modRange :: forall name. Module name -> Range
modRange Module name
m = [Range] -> Range
rCombs ([Range] -> Range) -> [Range] -> Range
forall a b. (a -> b) -> a -> b
$ [Maybe Range] -> [Range]
forall a. [Maybe a] -> [a]
catMaybes
[ Located ModName -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (Module name -> Located ModName
forall mname name. ModuleG mname name -> Located mname
mName Module name
m)
, [Located Import] -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (Module name -> [Located Import]
forall mname name. ModuleG mname name -> [Located Import]
mImports Module name
m)
, [TopDecl name] -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (Module name -> [TopDecl name]
forall mname name. ModuleG mname name -> [TopDecl name]
mDecls Module name
m)
, Range -> Maybe Range
forall a. a -> Maybe a
Just (Range { from :: Position
from = Position
start, to :: Position
to = Position
start, source :: String
source = String
"" })
]
data TopDecl name =
Decl (TopLevel (Decl name))
| DPrimType (TopLevel (PrimType name))
| TDNewtype (TopLevel (Newtype name))
| TDEnum (TopLevel (EnumDecl name))
| Include (Located FilePath)
| DParamDecl Range (Signature name)
| DModule (TopLevel (NestedModule name))
| DImport (Located (ImportG (ImpName name)))
| DModParam (ModParam name)
| DInterfaceConstraint (Maybe (Located Text)) (Located [Prop name])
deriving (Int -> TopDecl name -> ShowS
[TopDecl name] -> ShowS
TopDecl name -> String
(Int -> TopDecl name -> ShowS)
-> (TopDecl name -> String)
-> ([TopDecl name] -> ShowS)
-> Show (TopDecl name)
forall name. Show name => Int -> TopDecl name -> ShowS
forall name. Show name => [TopDecl name] -> ShowS
forall name. Show name => TopDecl name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> TopDecl name -> ShowS
showsPrec :: Int -> TopDecl name -> ShowS
$cshow :: forall name. Show name => TopDecl name -> String
show :: TopDecl name -> String
$cshowList :: forall name. Show name => [TopDecl name] -> ShowS
showList :: [TopDecl name] -> ShowS
Show, (forall x. TopDecl name -> Rep (TopDecl name) x)
-> (forall x. Rep (TopDecl name) x -> TopDecl name)
-> Generic (TopDecl name)
forall x. Rep (TopDecl name) x -> TopDecl name
forall x. TopDecl name -> Rep (TopDecl name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (TopDecl name) x -> TopDecl name
forall name x. TopDecl name -> Rep (TopDecl name) x
$cfrom :: forall name x. TopDecl name -> Rep (TopDecl name) x
from :: forall x. TopDecl name -> Rep (TopDecl name) x
$cto :: forall name x. Rep (TopDecl name) x -> TopDecl name
to :: forall x. Rep (TopDecl name) x -> TopDecl name
Generic, TopDecl name -> ()
(TopDecl name -> ()) -> NFData (TopDecl name)
forall name. NFData name => TopDecl name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => TopDecl name -> ()
rnf :: TopDecl name -> ()
NFData)
data ParamDecl name =
DParameterType (ParameterType name)
| DParameterFun (ParameterFun name)
| DParameterDecl (SigDecl name)
| DParameterConstraint (ParameterConstraint name)
deriving (Int -> ParamDecl name -> ShowS
[ParamDecl name] -> ShowS
ParamDecl name -> String
(Int -> ParamDecl name -> ShowS)
-> (ParamDecl name -> String)
-> ([ParamDecl name] -> ShowS)
-> Show (ParamDecl name)
forall name. Show name => Int -> ParamDecl name -> ShowS
forall name. Show name => [ParamDecl name] -> ShowS
forall name. Show name => ParamDecl name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> ParamDecl name -> ShowS
showsPrec :: Int -> ParamDecl name -> ShowS
$cshow :: forall name. Show name => ParamDecl name -> String
show :: ParamDecl name -> String
$cshowList :: forall name. Show name => [ParamDecl name] -> ShowS
showList :: [ParamDecl name] -> ShowS
Show, (forall x. ParamDecl name -> Rep (ParamDecl name) x)
-> (forall x. Rep (ParamDecl name) x -> ParamDecl name)
-> Generic (ParamDecl name)
forall x. Rep (ParamDecl name) x -> ParamDecl name
forall x. ParamDecl name -> Rep (ParamDecl name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (ParamDecl name) x -> ParamDecl name
forall name x. ParamDecl name -> Rep (ParamDecl name) x
$cfrom :: forall name x. ParamDecl name -> Rep (ParamDecl name) x
from :: forall x. ParamDecl name -> Rep (ParamDecl name) x
$cto :: forall name x. Rep (ParamDecl name) x -> ParamDecl name
to :: forall x. Rep (ParamDecl name) x -> ParamDecl name
Generic, ParamDecl name -> ()
(ParamDecl name -> ()) -> NFData (ParamDecl name)
forall name. NFData name => ParamDecl name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => ParamDecl name -> ()
rnf :: ParamDecl name -> ()
NFData)
data ModuleInstanceArgs name =
DefaultInstArg (Located (ModuleInstanceArg name))
| DefaultInstAnonArg [TopDecl name]
| NamedInstArgs [ModuleInstanceNamedArg name]
deriving (Int -> ModuleInstanceArgs name -> ShowS
[ModuleInstanceArgs name] -> ShowS
ModuleInstanceArgs name -> String
(Int -> ModuleInstanceArgs name -> ShowS)
-> (ModuleInstanceArgs name -> String)
-> ([ModuleInstanceArgs name] -> ShowS)
-> Show (ModuleInstanceArgs name)
forall name. Show name => Int -> ModuleInstanceArgs name -> ShowS
forall name. Show name => [ModuleInstanceArgs name] -> ShowS
forall name. Show name => ModuleInstanceArgs name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> ModuleInstanceArgs name -> ShowS
showsPrec :: Int -> ModuleInstanceArgs name -> ShowS
$cshow :: forall name. Show name => ModuleInstanceArgs name -> String
show :: ModuleInstanceArgs name -> String
$cshowList :: forall name. Show name => [ModuleInstanceArgs name] -> ShowS
showList :: [ModuleInstanceArgs name] -> ShowS
Show, (forall x.
ModuleInstanceArgs name -> Rep (ModuleInstanceArgs name) x)
-> (forall x.
Rep (ModuleInstanceArgs name) x -> ModuleInstanceArgs name)
-> Generic (ModuleInstanceArgs name)
forall x.
Rep (ModuleInstanceArgs name) x -> ModuleInstanceArgs name
forall x.
ModuleInstanceArgs name -> Rep (ModuleInstanceArgs name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x.
Rep (ModuleInstanceArgs name) x -> ModuleInstanceArgs name
forall name x.
ModuleInstanceArgs name -> Rep (ModuleInstanceArgs name) x
$cfrom :: forall name x.
ModuleInstanceArgs name -> Rep (ModuleInstanceArgs name) x
from :: forall x.
ModuleInstanceArgs name -> Rep (ModuleInstanceArgs name) x
$cto :: forall name x.
Rep (ModuleInstanceArgs name) x -> ModuleInstanceArgs name
to :: forall x.
Rep (ModuleInstanceArgs name) x -> ModuleInstanceArgs name
Generic, ModuleInstanceArgs name -> ()
(ModuleInstanceArgs name -> ()) -> NFData (ModuleInstanceArgs name)
forall name. NFData name => ModuleInstanceArgs name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => ModuleInstanceArgs name -> ()
rnf :: ModuleInstanceArgs name -> ()
NFData)
data ModuleInstanceNamedArg name =
ModuleInstanceNamedArg (Located Ident) (Located (ModuleInstanceArg name))
deriving (Int -> ModuleInstanceNamedArg name -> ShowS
[ModuleInstanceNamedArg name] -> ShowS
ModuleInstanceNamedArg name -> String
(Int -> ModuleInstanceNamedArg name -> ShowS)
-> (ModuleInstanceNamedArg name -> String)
-> ([ModuleInstanceNamedArg name] -> ShowS)
-> Show (ModuleInstanceNamedArg name)
forall name.
Show name =>
Int -> ModuleInstanceNamedArg name -> ShowS
forall name. Show name => [ModuleInstanceNamedArg name] -> ShowS
forall name. Show name => ModuleInstanceNamedArg name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name.
Show name =>
Int -> ModuleInstanceNamedArg name -> ShowS
showsPrec :: Int -> ModuleInstanceNamedArg name -> ShowS
$cshow :: forall name. Show name => ModuleInstanceNamedArg name -> String
show :: ModuleInstanceNamedArg name -> String
$cshowList :: forall name. Show name => [ModuleInstanceNamedArg name] -> ShowS
showList :: [ModuleInstanceNamedArg name] -> ShowS
Show, (forall x.
ModuleInstanceNamedArg name -> Rep (ModuleInstanceNamedArg name) x)
-> (forall x.
Rep (ModuleInstanceNamedArg name) x -> ModuleInstanceNamedArg name)
-> Generic (ModuleInstanceNamedArg name)
forall x.
Rep (ModuleInstanceNamedArg name) x -> ModuleInstanceNamedArg name
forall x.
ModuleInstanceNamedArg name -> Rep (ModuleInstanceNamedArg name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x.
Rep (ModuleInstanceNamedArg name) x -> ModuleInstanceNamedArg name
forall name x.
ModuleInstanceNamedArg name -> Rep (ModuleInstanceNamedArg name) x
$cfrom :: forall name x.
ModuleInstanceNamedArg name -> Rep (ModuleInstanceNamedArg name) x
from :: forall x.
ModuleInstanceNamedArg name -> Rep (ModuleInstanceNamedArg name) x
$cto :: forall name x.
Rep (ModuleInstanceNamedArg name) x -> ModuleInstanceNamedArg name
to :: forall x.
Rep (ModuleInstanceNamedArg name) x -> ModuleInstanceNamedArg name
Generic, ModuleInstanceNamedArg name -> ()
(ModuleInstanceNamedArg name -> ())
-> NFData (ModuleInstanceNamedArg name)
forall name. NFData name => ModuleInstanceNamedArg name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => ModuleInstanceNamedArg name -> ()
rnf :: ModuleInstanceNamedArg name -> ()
NFData)
data ModuleInstanceArg name =
ModuleArg (ImpName name)
| ParameterArg Ident
| AddParams
deriving (Int -> ModuleInstanceArg name -> ShowS
[ModuleInstanceArg name] -> ShowS
ModuleInstanceArg name -> String
(Int -> ModuleInstanceArg name -> ShowS)
-> (ModuleInstanceArg name -> String)
-> ([ModuleInstanceArg name] -> ShowS)
-> Show (ModuleInstanceArg name)
forall name. Show name => Int -> ModuleInstanceArg name -> ShowS
forall name. Show name => [ModuleInstanceArg name] -> ShowS
forall name. Show name => ModuleInstanceArg name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> ModuleInstanceArg name -> ShowS
showsPrec :: Int -> ModuleInstanceArg name -> ShowS
$cshow :: forall name. Show name => ModuleInstanceArg name -> String
show :: ModuleInstanceArg name -> String
$cshowList :: forall name. Show name => [ModuleInstanceArg name] -> ShowS
showList :: [ModuleInstanceArg name] -> ShowS
Show, (forall x.
ModuleInstanceArg name -> Rep (ModuleInstanceArg name) x)
-> (forall x.
Rep (ModuleInstanceArg name) x -> ModuleInstanceArg name)
-> Generic (ModuleInstanceArg name)
forall x. Rep (ModuleInstanceArg name) x -> ModuleInstanceArg name
forall x. ModuleInstanceArg name -> Rep (ModuleInstanceArg name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x.
Rep (ModuleInstanceArg name) x -> ModuleInstanceArg name
forall name x.
ModuleInstanceArg name -> Rep (ModuleInstanceArg name) x
$cfrom :: forall name x.
ModuleInstanceArg name -> Rep (ModuleInstanceArg name) x
from :: forall x. ModuleInstanceArg name -> Rep (ModuleInstanceArg name) x
$cto :: forall name x.
Rep (ModuleInstanceArg name) x -> ModuleInstanceArg name
to :: forall x. Rep (ModuleInstanceArg name) x -> ModuleInstanceArg name
Generic, ModuleInstanceArg name -> ()
(ModuleInstanceArg name -> ()) -> NFData (ModuleInstanceArg name)
forall name. NFData name => ModuleInstanceArg name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => ModuleInstanceArg name -> ()
rnf :: ModuleInstanceArg name -> ()
NFData)
data ImpName name =
ImpTop ModName
| ImpNested name
deriving (Int -> ImpName name -> ShowS
[ImpName name] -> ShowS
ImpName name -> String
(Int -> ImpName name -> ShowS)
-> (ImpName name -> String)
-> ([ImpName name] -> ShowS)
-> Show (ImpName name)
forall name. Show name => Int -> ImpName name -> ShowS
forall name. Show name => [ImpName name] -> ShowS
forall name. Show name => ImpName name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> ImpName name -> ShowS
showsPrec :: Int -> ImpName name -> ShowS
$cshow :: forall name. Show name => ImpName name -> String
show :: ImpName name -> String
$cshowList :: forall name. Show name => [ImpName name] -> ShowS
showList :: [ImpName name] -> ShowS
Show, (forall x. ImpName name -> Rep (ImpName name) x)
-> (forall x. Rep (ImpName name) x -> ImpName name)
-> Generic (ImpName name)
forall x. Rep (ImpName name) x -> ImpName name
forall x. ImpName name -> Rep (ImpName name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (ImpName name) x -> ImpName name
forall name x. ImpName name -> Rep (ImpName name) x
$cfrom :: forall name x. ImpName name -> Rep (ImpName name) x
from :: forall x. ImpName name -> Rep (ImpName name) x
$cto :: forall name x. Rep (ImpName name) x -> ImpName name
to :: forall x. Rep (ImpName name) x -> ImpName name
Generic, ImpName name -> ()
(ImpName name -> ()) -> NFData (ImpName name)
forall name. NFData name => ImpName name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => ImpName name -> ()
rnf :: ImpName name -> ()
NFData, ImpName name -> ImpName name -> Bool
(ImpName name -> ImpName name -> Bool)
-> (ImpName name -> ImpName name -> Bool) -> Eq (ImpName name)
forall name. Eq name => ImpName name -> ImpName name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name. Eq name => ImpName name -> ImpName name -> Bool
== :: ImpName name -> ImpName name -> Bool
$c/= :: forall name. Eq name => ImpName name -> ImpName name -> Bool
/= :: ImpName name -> ImpName name -> Bool
Eq, Eq (ImpName name)
Eq (ImpName name) =>
(ImpName name -> ImpName name -> Ordering)
-> (ImpName name -> ImpName name -> Bool)
-> (ImpName name -> ImpName name -> Bool)
-> (ImpName name -> ImpName name -> Bool)
-> (ImpName name -> ImpName name -> Bool)
-> (ImpName name -> ImpName name -> ImpName name)
-> (ImpName name -> ImpName name -> ImpName name)
-> Ord (ImpName name)
ImpName name -> ImpName name -> Bool
ImpName name -> ImpName name -> Ordering
ImpName name -> ImpName name -> ImpName 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
forall name. Ord name => Eq (ImpName name)
forall name. Ord name => ImpName name -> ImpName name -> Bool
forall name. Ord name => ImpName name -> ImpName name -> Ordering
forall name.
Ord name =>
ImpName name -> ImpName name -> ImpName name
$ccompare :: forall name. Ord name => ImpName name -> ImpName name -> Ordering
compare :: ImpName name -> ImpName name -> Ordering
$c< :: forall name. Ord name => ImpName name -> ImpName name -> Bool
< :: ImpName name -> ImpName name -> Bool
$c<= :: forall name. Ord name => ImpName name -> ImpName name -> Bool
<= :: ImpName name -> ImpName name -> Bool
$c> :: forall name. Ord name => ImpName name -> ImpName name -> Bool
> :: ImpName name -> ImpName name -> Bool
$c>= :: forall name. Ord name => ImpName name -> ImpName name -> Bool
>= :: ImpName name -> ImpName name -> Bool
$cmax :: forall name.
Ord name =>
ImpName name -> ImpName name -> ImpName name
max :: ImpName name -> ImpName name -> ImpName name
$cmin :: forall name.
Ord name =>
ImpName name -> ImpName name -> ImpName name
min :: ImpName name -> ImpName name -> ImpName name
Ord)
impNameModPath :: ImpName Name -> ModPath
impNameModPath :: ImpName Name -> ModPath
impNameModPath (ImpTop ModName
mn) = ModName -> ModPath
TopModule ModName
mn
impNameModPath (ImpNested Name
n) = ModPath -> Ident -> ModPath
Nested (Name -> ModPath
nameModPath Name
n) (Name -> Ident
nameIdent Name
n)
data Decl name = DSignature [Located name] (Schema name)
| DFixity !Fixity [Located name]
| DPragma [Located name] Pragma
| DBind (Bind name)
| DRec [Bind name]
| DPatBind (Pattern name) (Expr name)
| DType (TySyn name)
| DProp (PropSyn name)
| DLocated (Decl name) Range
deriving (Decl name -> Decl name -> Bool
(Decl name -> Decl name -> Bool)
-> (Decl name -> Decl name -> Bool) -> Eq (Decl name)
forall name. Eq name => Decl name -> Decl name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name. Eq name => Decl name -> Decl name -> Bool
== :: Decl name -> Decl name -> Bool
$c/= :: forall name. Eq name => Decl name -> Decl name -> Bool
/= :: Decl name -> Decl name -> Bool
Eq, Int -> Decl name -> ShowS
[Decl name] -> ShowS
Decl name -> String
(Int -> Decl name -> ShowS)
-> (Decl name -> String)
-> ([Decl name] -> ShowS)
-> Show (Decl name)
forall name. Show name => Int -> Decl name -> ShowS
forall name. Show name => [Decl name] -> ShowS
forall name. Show name => Decl name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> Decl name -> ShowS
showsPrec :: Int -> Decl name -> ShowS
$cshow :: forall name. Show name => Decl name -> String
show :: Decl name -> String
$cshowList :: forall name. Show name => [Decl name] -> ShowS
showList :: [Decl name] -> ShowS
Show, (forall x. Decl name -> Rep (Decl name) x)
-> (forall x. Rep (Decl name) x -> Decl name)
-> Generic (Decl name)
forall x. Rep (Decl name) x -> Decl name
forall x. Decl name -> Rep (Decl name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (Decl name) x -> Decl name
forall name x. Decl name -> Rep (Decl name) x
$cfrom :: forall name x. Decl name -> Rep (Decl name) x
from :: forall x. Decl name -> Rep (Decl name) x
$cto :: forall name x. Rep (Decl name) x -> Decl name
to :: forall x. Rep (Decl name) x -> Decl name
Generic, Decl name -> ()
(Decl name -> ()) -> NFData (Decl name)
forall name. NFData name => Decl name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => Decl name -> ()
rnf :: Decl name -> ()
NFData, (forall a b. (a -> b) -> Decl a -> Decl b)
-> (forall a b. a -> Decl b -> Decl a) -> Functor Decl
forall a b. a -> Decl b -> Decl a
forall a b. (a -> b) -> Decl a -> Decl b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Decl a -> Decl b
fmap :: forall a b. (a -> b) -> Decl a -> Decl b
$c<$ :: forall a b. a -> Decl b -> Decl a
<$ :: forall a b. a -> Decl b -> Decl a
Functor)
data ParameterType name = ParameterType
{ forall name. ParameterType name -> Located name
ptName :: Located name
, forall name. ParameterType name -> Kind
ptKind :: Kind
, forall name. ParameterType name -> Maybe (Located Text)
ptDoc :: Maybe (Located Text)
, forall name. ParameterType name -> Maybe Fixity
ptFixity :: Maybe Fixity
, forall name. ParameterType name -> Int
ptNumber :: !Int
} deriving (ParameterType name -> ParameterType name -> Bool
(ParameterType name -> ParameterType name -> Bool)
-> (ParameterType name -> ParameterType name -> Bool)
-> Eq (ParameterType name)
forall name.
Eq name =>
ParameterType name -> ParameterType name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name.
Eq name =>
ParameterType name -> ParameterType name -> Bool
== :: ParameterType name -> ParameterType name -> Bool
$c/= :: forall name.
Eq name =>
ParameterType name -> ParameterType name -> Bool
/= :: ParameterType name -> ParameterType name -> Bool
Eq,Int -> ParameterType name -> ShowS
[ParameterType name] -> ShowS
ParameterType name -> String
(Int -> ParameterType name -> ShowS)
-> (ParameterType name -> String)
-> ([ParameterType name] -> ShowS)
-> Show (ParameterType name)
forall name. Show name => Int -> ParameterType name -> ShowS
forall name. Show name => [ParameterType name] -> ShowS
forall name. Show name => ParameterType name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> ParameterType name -> ShowS
showsPrec :: Int -> ParameterType name -> ShowS
$cshow :: forall name. Show name => ParameterType name -> String
show :: ParameterType name -> String
$cshowList :: forall name. Show name => [ParameterType name] -> ShowS
showList :: [ParameterType name] -> ShowS
Show,(forall x. ParameterType name -> Rep (ParameterType name) x)
-> (forall x. Rep (ParameterType name) x -> ParameterType name)
-> Generic (ParameterType name)
forall x. Rep (ParameterType name) x -> ParameterType name
forall x. ParameterType name -> Rep (ParameterType name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (ParameterType name) x -> ParameterType name
forall name x. ParameterType name -> Rep (ParameterType name) x
$cfrom :: forall name x. ParameterType name -> Rep (ParameterType name) x
from :: forall x. ParameterType name -> Rep (ParameterType name) x
$cto :: forall name x. Rep (ParameterType name) x -> ParameterType name
to :: forall x. Rep (ParameterType name) x -> ParameterType name
Generic,ParameterType name -> ()
(ParameterType name -> ()) -> NFData (ParameterType name)
forall name. NFData name => ParameterType name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => ParameterType name -> ()
rnf :: ParameterType name -> ()
NFData)
data ParameterFun name = ParameterFun
{ forall name. ParameterFun name -> Located name
pfName :: Located name
, forall name. ParameterFun name -> Schema name
pfSchema :: Schema name
, forall name. ParameterFun name -> Maybe (Located Text)
pfDoc :: Maybe (Located Text)
, forall name. ParameterFun name -> Maybe Fixity
pfFixity :: Maybe Fixity
} deriving (ParameterFun name -> ParameterFun name -> Bool
(ParameterFun name -> ParameterFun name -> Bool)
-> (ParameterFun name -> ParameterFun name -> Bool)
-> Eq (ParameterFun name)
forall name.
Eq name =>
ParameterFun name -> ParameterFun name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name.
Eq name =>
ParameterFun name -> ParameterFun name -> Bool
== :: ParameterFun name -> ParameterFun name -> Bool
$c/= :: forall name.
Eq name =>
ParameterFun name -> ParameterFun name -> Bool
/= :: ParameterFun name -> ParameterFun name -> Bool
Eq,Int -> ParameterFun name -> ShowS
[ParameterFun name] -> ShowS
ParameterFun name -> String
(Int -> ParameterFun name -> ShowS)
-> (ParameterFun name -> String)
-> ([ParameterFun name] -> ShowS)
-> Show (ParameterFun name)
forall name. Show name => Int -> ParameterFun name -> ShowS
forall name. Show name => [ParameterFun name] -> ShowS
forall name. Show name => ParameterFun name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> ParameterFun name -> ShowS
showsPrec :: Int -> ParameterFun name -> ShowS
$cshow :: forall name. Show name => ParameterFun name -> String
show :: ParameterFun name -> String
$cshowList :: forall name. Show name => [ParameterFun name] -> ShowS
showList :: [ParameterFun name] -> ShowS
Show,(forall x. ParameterFun name -> Rep (ParameterFun name) x)
-> (forall x. Rep (ParameterFun name) x -> ParameterFun name)
-> Generic (ParameterFun name)
forall x. Rep (ParameterFun name) x -> ParameterFun name
forall x. ParameterFun name -> Rep (ParameterFun name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (ParameterFun name) x -> ParameterFun name
forall name x. ParameterFun name -> Rep (ParameterFun name) x
$cfrom :: forall name x. ParameterFun name -> Rep (ParameterFun name) x
from :: forall x. ParameterFun name -> Rep (ParameterFun name) x
$cto :: forall name x. Rep (ParameterFun name) x -> ParameterFun name
to :: forall x. Rep (ParameterFun name) x -> ParameterFun name
Generic,ParameterFun name -> ()
(ParameterFun name -> ()) -> NFData (ParameterFun name)
forall name. NFData name => ParameterFun name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => ParameterFun name -> ()
rnf :: ParameterFun name -> ()
NFData)
data ParameterConstraint name = ParameterConstraint
{ forall name. ParameterConstraint name -> [Located (Prop name)]
pcProps :: [Located (Prop name)]
, forall name. ParameterConstraint name -> Maybe (Located Text)
pcDoc :: Maybe (Located Text)
} deriving (ParameterConstraint name -> ParameterConstraint name -> Bool
(ParameterConstraint name -> ParameterConstraint name -> Bool)
-> (ParameterConstraint name -> ParameterConstraint name -> Bool)
-> Eq (ParameterConstraint name)
forall name.
Eq name =>
ParameterConstraint name -> ParameterConstraint name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name.
Eq name =>
ParameterConstraint name -> ParameterConstraint name -> Bool
== :: ParameterConstraint name -> ParameterConstraint name -> Bool
$c/= :: forall name.
Eq name =>
ParameterConstraint name -> ParameterConstraint name -> Bool
/= :: ParameterConstraint name -> ParameterConstraint name -> Bool
Eq,Int -> ParameterConstraint name -> ShowS
[ParameterConstraint name] -> ShowS
ParameterConstraint name -> String
(Int -> ParameterConstraint name -> ShowS)
-> (ParameterConstraint name -> String)
-> ([ParameterConstraint name] -> ShowS)
-> Show (ParameterConstraint name)
forall name. Show name => Int -> ParameterConstraint name -> ShowS
forall name. Show name => [ParameterConstraint name] -> ShowS
forall name. Show name => ParameterConstraint name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> ParameterConstraint name -> ShowS
showsPrec :: Int -> ParameterConstraint name -> ShowS
$cshow :: forall name. Show name => ParameterConstraint name -> String
show :: ParameterConstraint name -> String
$cshowList :: forall name. Show name => [ParameterConstraint name] -> ShowS
showList :: [ParameterConstraint name] -> ShowS
Show,(forall x.
ParameterConstraint name -> Rep (ParameterConstraint name) x)
-> (forall x.
Rep (ParameterConstraint name) x -> ParameterConstraint name)
-> Generic (ParameterConstraint name)
forall x.
Rep (ParameterConstraint name) x -> ParameterConstraint name
forall x.
ParameterConstraint name -> Rep (ParameterConstraint name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x.
Rep (ParameterConstraint name) x -> ParameterConstraint name
forall name x.
ParameterConstraint name -> Rep (ParameterConstraint name) x
$cfrom :: forall name x.
ParameterConstraint name -> Rep (ParameterConstraint name) x
from :: forall x.
ParameterConstraint name -> Rep (ParameterConstraint name) x
$cto :: forall name x.
Rep (ParameterConstraint name) x -> ParameterConstraint name
to :: forall x.
Rep (ParameterConstraint name) x -> ParameterConstraint name
Generic,ParameterConstraint name -> ()
(ParameterConstraint name -> ())
-> NFData (ParameterConstraint name)
forall name. NFData name => ParameterConstraint name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => ParameterConstraint name -> ()
rnf :: ParameterConstraint name -> ()
NFData)
data Signature name = Signature
{ forall name. Signature name -> [Located (ImportG (ImpName name))]
sigImports :: ![Located (ImportG (ImpName name))]
, forall name. Signature name -> [ParameterType name]
sigTypeParams :: [ParameterType name]
, forall name. Signature name -> [Located (Prop name)]
sigConstraints :: [Located (Prop name)]
, forall name. Signature name -> [SigDecl name]
sigDecls :: [SigDecl name]
, forall name. Signature name -> [ParameterFun name]
sigFunParams :: [ParameterFun name]
} deriving (Int -> Signature name -> ShowS
[Signature name] -> ShowS
Signature name -> String
(Int -> Signature name -> ShowS)
-> (Signature name -> String)
-> ([Signature name] -> ShowS)
-> Show (Signature name)
forall name. Show name => Int -> Signature name -> ShowS
forall name. Show name => [Signature name] -> ShowS
forall name. Show name => Signature name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> Signature name -> ShowS
showsPrec :: Int -> Signature name -> ShowS
$cshow :: forall name. Show name => Signature name -> String
show :: Signature name -> String
$cshowList :: forall name. Show name => [Signature name] -> ShowS
showList :: [Signature name] -> ShowS
Show,(forall x. Signature name -> Rep (Signature name) x)
-> (forall x. Rep (Signature name) x -> Signature name)
-> Generic (Signature name)
forall x. Rep (Signature name) x -> Signature name
forall x. Signature name -> Rep (Signature name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (Signature name) x -> Signature name
forall name x. Signature name -> Rep (Signature name) x
$cfrom :: forall name x. Signature name -> Rep (Signature name) x
from :: forall x. Signature name -> Rep (Signature name) x
$cto :: forall name x. Rep (Signature name) x -> Signature name
to :: forall x. Rep (Signature name) x -> Signature name
Generic,Signature name -> ()
(Signature name -> ()) -> NFData (Signature name)
forall name. NFData name => Signature name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => Signature name -> ()
rnf :: Signature name -> ()
NFData)
data SigDecl name =
SigTySyn (TySyn name) (Maybe Text)
| SigPropSyn (PropSyn name) (Maybe Text)
deriving (Int -> SigDecl name -> ShowS
[SigDecl name] -> ShowS
SigDecl name -> String
(Int -> SigDecl name -> ShowS)
-> (SigDecl name -> String)
-> ([SigDecl name] -> ShowS)
-> Show (SigDecl name)
forall name. Show name => Int -> SigDecl name -> ShowS
forall name. Show name => [SigDecl name] -> ShowS
forall name. Show name => SigDecl name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> SigDecl name -> ShowS
showsPrec :: Int -> SigDecl name -> ShowS
$cshow :: forall name. Show name => SigDecl name -> String
show :: SigDecl name -> String
$cshowList :: forall name. Show name => [SigDecl name] -> ShowS
showList :: [SigDecl name] -> ShowS
Show,(forall x. SigDecl name -> Rep (SigDecl name) x)
-> (forall x. Rep (SigDecl name) x -> SigDecl name)
-> Generic (SigDecl name)
forall x. Rep (SigDecl name) x -> SigDecl name
forall x. SigDecl name -> Rep (SigDecl name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (SigDecl name) x -> SigDecl name
forall name x. SigDecl name -> Rep (SigDecl name) x
$cfrom :: forall name x. SigDecl name -> Rep (SigDecl name) x
from :: forall x. SigDecl name -> Rep (SigDecl name) x
$cto :: forall name x. Rep (SigDecl name) x -> SigDecl name
to :: forall x. Rep (SigDecl name) x -> SigDecl name
Generic,SigDecl name -> ()
(SigDecl name -> ()) -> NFData (SigDecl name)
forall name. NFData name => SigDecl name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => SigDecl name -> ()
rnf :: SigDecl name -> ()
NFData)
data ModParam name = ModParam
{ forall name. ModParam name -> Located (ImpName name)
mpSignature :: Located (ImpName name)
, forall name. ModParam name -> Maybe ModName
mpAs :: Maybe ModName
, forall name. ModParam name -> Ident
mpName :: !Ident
, forall name. ModParam name -> Maybe (Located Text)
mpDoc :: Maybe (Located Text)
, forall name. ModParam name -> Map name name
mpRenaming :: !(Map name name)
} deriving (ModParam name -> ModParam name -> Bool
(ModParam name -> ModParam name -> Bool)
-> (ModParam name -> ModParam name -> Bool) -> Eq (ModParam name)
forall name. Eq name => ModParam name -> ModParam name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name. Eq name => ModParam name -> ModParam name -> Bool
== :: ModParam name -> ModParam name -> Bool
$c/= :: forall name. Eq name => ModParam name -> ModParam name -> Bool
/= :: ModParam name -> ModParam name -> Bool
Eq,Int -> ModParam name -> ShowS
[ModParam name] -> ShowS
ModParam name -> String
(Int -> ModParam name -> ShowS)
-> (ModParam name -> String)
-> ([ModParam name] -> ShowS)
-> Show (ModParam name)
forall name. Show name => Int -> ModParam name -> ShowS
forall name. Show name => [ModParam name] -> ShowS
forall name. Show name => ModParam name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> ModParam name -> ShowS
showsPrec :: Int -> ModParam name -> ShowS
$cshow :: forall name. Show name => ModParam name -> String
show :: ModParam name -> String
$cshowList :: forall name. Show name => [ModParam name] -> ShowS
showList :: [ModParam name] -> ShowS
Show,(forall x. ModParam name -> Rep (ModParam name) x)
-> (forall x. Rep (ModParam name) x -> ModParam name)
-> Generic (ModParam name)
forall x. Rep (ModParam name) x -> ModParam name
forall x. ModParam name -> Rep (ModParam name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (ModParam name) x -> ModParam name
forall name x. ModParam name -> Rep (ModParam name) x
$cfrom :: forall name x. ModParam name -> Rep (ModParam name) x
from :: forall x. ModParam name -> Rep (ModParam name) x
$cto :: forall name x. Rep (ModParam name) x -> ModParam name
to :: forall x. Rep (ModParam name) x -> ModParam name
Generic,ModParam name -> ()
(ModParam name -> ()) -> NFData (ModParam name)
forall name. NFData name => ModParam name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => ModParam name -> ()
rnf :: ModParam name -> ()
NFData)
data ImportG mname = Import
{ forall mname. ImportG mname -> mname
iModule :: !mname
, forall mname. ImportG mname -> Maybe ModName
iAs :: Maybe ModName
, forall mname. ImportG mname -> Maybe ImportSpec
iSpec :: Maybe ImportSpec
, forall mname. ImportG mname -> Maybe (ModuleInstanceArgs PName)
iInst :: !(Maybe (ModuleInstanceArgs PName))
, forall mname. ImportG mname -> Maybe (Located Text)
iDoc :: Maybe (Located Text)
} deriving (Int -> ImportG mname -> ShowS
[ImportG mname] -> ShowS
ImportG mname -> String
(Int -> ImportG mname -> ShowS)
-> (ImportG mname -> String)
-> ([ImportG mname] -> ShowS)
-> Show (ImportG mname)
forall mname. Show mname => Int -> ImportG mname -> ShowS
forall mname. Show mname => [ImportG mname] -> ShowS
forall mname. Show mname => ImportG mname -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall mname. Show mname => Int -> ImportG mname -> ShowS
showsPrec :: Int -> ImportG mname -> ShowS
$cshow :: forall mname. Show mname => ImportG mname -> String
show :: ImportG mname -> String
$cshowList :: forall mname. Show mname => [ImportG mname] -> ShowS
showList :: [ImportG mname] -> ShowS
Show, (forall x. ImportG mname -> Rep (ImportG mname) x)
-> (forall x. Rep (ImportG mname) x -> ImportG mname)
-> Generic (ImportG mname)
forall x. Rep (ImportG mname) x -> ImportG mname
forall x. ImportG mname -> Rep (ImportG mname) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall mname x. Rep (ImportG mname) x -> ImportG mname
forall mname x. ImportG mname -> Rep (ImportG mname) x
$cfrom :: forall mname x. ImportG mname -> Rep (ImportG mname) x
from :: forall x. ImportG mname -> Rep (ImportG mname) x
$cto :: forall mname x. Rep (ImportG mname) x -> ImportG mname
to :: forall x. Rep (ImportG mname) x -> ImportG mname
Generic, ImportG mname -> ()
(ImportG mname -> ()) -> NFData (ImportG mname)
forall mname. NFData mname => ImportG mname -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall mname. NFData mname => ImportG mname -> ()
rnf :: ImportG mname -> ()
NFData)
type Import = ImportG ModName
data ImportSpec = Hiding [Ident]
| Only [Ident]
deriving (ImportSpec -> ImportSpec -> Bool
(ImportSpec -> ImportSpec -> Bool)
-> (ImportSpec -> ImportSpec -> Bool) -> Eq ImportSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImportSpec -> ImportSpec -> Bool
== :: ImportSpec -> ImportSpec -> Bool
$c/= :: ImportSpec -> ImportSpec -> Bool
/= :: ImportSpec -> ImportSpec -> Bool
Eq, Int -> ImportSpec -> ShowS
[ImportSpec] -> ShowS
ImportSpec -> String
(Int -> ImportSpec -> ShowS)
-> (ImportSpec -> String)
-> ([ImportSpec] -> ShowS)
-> Show ImportSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ImportSpec -> ShowS
showsPrec :: Int -> ImportSpec -> ShowS
$cshow :: ImportSpec -> String
show :: ImportSpec -> String
$cshowList :: [ImportSpec] -> ShowS
showList :: [ImportSpec] -> ShowS
Show, (forall x. ImportSpec -> Rep ImportSpec x)
-> (forall x. Rep ImportSpec x -> ImportSpec) -> Generic ImportSpec
forall x. Rep ImportSpec x -> ImportSpec
forall x. ImportSpec -> Rep ImportSpec x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ImportSpec -> Rep ImportSpec x
from :: forall x. ImportSpec -> Rep ImportSpec x
$cto :: forall x. Rep ImportSpec x -> ImportSpec
to :: forall x. Rep ImportSpec x -> ImportSpec
Generic, ImportSpec -> ()
(ImportSpec -> ()) -> NFData ImportSpec
forall a. (a -> ()) -> NFData a
$crnf :: ImportSpec -> ()
rnf :: ImportSpec -> ()
NFData)
data TySyn n = TySyn (Located n) (Maybe Fixity) [TParam n] (Type n)
deriving (TySyn n -> TySyn n -> Bool
(TySyn n -> TySyn n -> Bool)
-> (TySyn n -> TySyn n -> Bool) -> Eq (TySyn n)
forall n. Eq n => TySyn n -> TySyn n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n. Eq n => TySyn n -> TySyn n -> Bool
== :: TySyn n -> TySyn n -> Bool
$c/= :: forall n. Eq n => TySyn n -> TySyn n -> Bool
/= :: TySyn n -> TySyn n -> Bool
Eq, Int -> TySyn n -> ShowS
[TySyn n] -> ShowS
TySyn n -> String
(Int -> TySyn n -> ShowS)
-> (TySyn n -> String) -> ([TySyn n] -> ShowS) -> Show (TySyn n)
forall n. Show n => Int -> TySyn n -> ShowS
forall n. Show n => [TySyn n] -> ShowS
forall n. Show n => TySyn n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> TySyn n -> ShowS
showsPrec :: Int -> TySyn n -> ShowS
$cshow :: forall n. Show n => TySyn n -> String
show :: TySyn n -> String
$cshowList :: forall n. Show n => [TySyn n] -> ShowS
showList :: [TySyn n] -> ShowS
Show, (forall x. TySyn n -> Rep (TySyn n) x)
-> (forall x. Rep (TySyn n) x -> TySyn n) -> Generic (TySyn n)
forall x. Rep (TySyn n) x -> TySyn n
forall x. TySyn n -> Rep (TySyn n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (TySyn n) x -> TySyn n
forall n x. TySyn n -> Rep (TySyn n) x
$cfrom :: forall n x. TySyn n -> Rep (TySyn n) x
from :: forall x. TySyn n -> Rep (TySyn n) x
$cto :: forall n x. Rep (TySyn n) x -> TySyn n
to :: forall x. Rep (TySyn n) x -> TySyn n
Generic, TySyn n -> ()
(TySyn n -> ()) -> NFData (TySyn n)
forall n. NFData n => TySyn n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => TySyn n -> ()
rnf :: TySyn n -> ()
NFData, (forall a b. (a -> b) -> TySyn a -> TySyn b)
-> (forall a b. a -> TySyn b -> TySyn a) -> Functor TySyn
forall a b. a -> TySyn b -> TySyn a
forall a b. (a -> b) -> TySyn a -> TySyn b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> TySyn a -> TySyn b
fmap :: forall a b. (a -> b) -> TySyn a -> TySyn b
$c<$ :: forall a b. a -> TySyn b -> TySyn a
<$ :: forall a b. a -> TySyn b -> TySyn a
Functor)
data PropSyn n = PropSyn (Located n) (Maybe Fixity) [TParam n] [Prop n]
deriving (PropSyn n -> PropSyn n -> Bool
(PropSyn n -> PropSyn n -> Bool)
-> (PropSyn n -> PropSyn n -> Bool) -> Eq (PropSyn n)
forall n. Eq n => PropSyn n -> PropSyn n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n. Eq n => PropSyn n -> PropSyn n -> Bool
== :: PropSyn n -> PropSyn n -> Bool
$c/= :: forall n. Eq n => PropSyn n -> PropSyn n -> Bool
/= :: PropSyn n -> PropSyn n -> Bool
Eq, Int -> PropSyn n -> ShowS
[PropSyn n] -> ShowS
PropSyn n -> String
(Int -> PropSyn n -> ShowS)
-> (PropSyn n -> String)
-> ([PropSyn n] -> ShowS)
-> Show (PropSyn n)
forall n. Show n => Int -> PropSyn n -> ShowS
forall n. Show n => [PropSyn n] -> ShowS
forall n. Show n => PropSyn n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> PropSyn n -> ShowS
showsPrec :: Int -> PropSyn n -> ShowS
$cshow :: forall n. Show n => PropSyn n -> String
show :: PropSyn n -> String
$cshowList :: forall n. Show n => [PropSyn n] -> ShowS
showList :: [PropSyn n] -> ShowS
Show, (forall x. PropSyn n -> Rep (PropSyn n) x)
-> (forall x. Rep (PropSyn n) x -> PropSyn n)
-> Generic (PropSyn n)
forall x. Rep (PropSyn n) x -> PropSyn n
forall x. PropSyn n -> Rep (PropSyn n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (PropSyn n) x -> PropSyn n
forall n x. PropSyn n -> Rep (PropSyn n) x
$cfrom :: forall n x. PropSyn n -> Rep (PropSyn n) x
from :: forall x. PropSyn n -> Rep (PropSyn n) x
$cto :: forall n x. Rep (PropSyn n) x -> PropSyn n
to :: forall x. Rep (PropSyn n) x -> PropSyn n
Generic, PropSyn n -> ()
(PropSyn n -> ()) -> NFData (PropSyn n)
forall n. NFData n => PropSyn n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => PropSyn n -> ()
rnf :: PropSyn n -> ()
NFData, (forall a b. (a -> b) -> PropSyn a -> PropSyn b)
-> (forall a b. a -> PropSyn b -> PropSyn a) -> Functor PropSyn
forall a b. a -> PropSyn b -> PropSyn a
forall a b. (a -> b) -> PropSyn a -> PropSyn b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> PropSyn a -> PropSyn b
fmap :: forall a b. (a -> b) -> PropSyn a -> PropSyn b
$c<$ :: forall a b. a -> PropSyn b -> PropSyn a
<$ :: forall a b. a -> PropSyn b -> PropSyn a
Functor)
tsName :: TySyn name -> Located name
tsName :: forall name. TySyn name -> Located name
tsName (TySyn Located name
lqn Maybe Fixity
_ [TParam name]
_ Type name
_) = Located name
lqn
psName :: PropSyn name -> Located name
psName :: forall name. PropSyn name -> Located name
psName (PropSyn Located name
lqn Maybe Fixity
_ [TParam name]
_ [Prop name]
_) = Located name
lqn
tsFixity :: TySyn name -> Maybe Fixity
tsFixity :: forall name. TySyn name -> Maybe Fixity
tsFixity (TySyn Located name
_ Maybe Fixity
f [TParam name]
_ Type name
_) = Maybe Fixity
f
psFixity :: PropSyn name -> Maybe Fixity
psFixity :: forall name. PropSyn name -> Maybe Fixity
psFixity (PropSyn Located name
_ Maybe Fixity
f [TParam name]
_ [Prop name]
_) = Maybe Fixity
f
data Bind name = Bind
{ forall name. Bind name -> Located name
bName :: Located name
, forall name. Bind name -> BindParams name
bParams :: BindParams name
, forall name. Bind name -> Located (BindDef name)
bDef :: Located (BindDef name)
, forall name. Bind name -> Maybe (Schema name)
bSignature :: Maybe (Schema name)
, forall name. Bind name -> Bool
bInfix :: Bool
, forall name. Bind name -> Maybe Fixity
bFixity :: Maybe Fixity
, forall name. Bind name -> [Pragma]
bPragmas :: [Pragma]
, forall name. Bind name -> Bool
bMono :: Bool
, forall name. Bind name -> Maybe (Located Text)
bDoc :: Maybe (Located Text)
, forall name. Bind name -> ExportType
bExport :: !ExportType
} deriving (Bind name -> Bind name -> Bool
(Bind name -> Bind name -> Bool)
-> (Bind name -> Bind name -> Bool) -> Eq (Bind name)
forall name. Eq name => Bind name -> Bind name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name. Eq name => Bind name -> Bind name -> Bool
== :: Bind name -> Bind name -> Bool
$c/= :: forall name. Eq name => Bind name -> Bind name -> Bool
/= :: Bind name -> Bind name -> Bool
Eq, (forall x. Bind name -> Rep (Bind name) x)
-> (forall x. Rep (Bind name) x -> Bind name)
-> Generic (Bind name)
forall x. Rep (Bind name) x -> Bind name
forall x. Bind name -> Rep (Bind name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (Bind name) x -> Bind name
forall name x. Bind name -> Rep (Bind name) x
$cfrom :: forall name x. Bind name -> Rep (Bind name) x
from :: forall x. Bind name -> Rep (Bind name) x
$cto :: forall name x. Rep (Bind name) x -> Bind name
to :: forall x. Rep (Bind name) x -> Bind name
Generic, Bind name -> ()
(Bind name -> ()) -> NFData (Bind name)
forall name. NFData name => Bind name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => Bind name -> ()
rnf :: Bind name -> ()
NFData, (forall a b. (a -> b) -> Bind a -> Bind b)
-> (forall a b. a -> Bind b -> Bind a) -> Functor Bind
forall a b. a -> Bind b -> Bind a
forall a b. (a -> b) -> Bind a -> Bind b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Bind a -> Bind b
fmap :: forall a b. (a -> b) -> Bind a -> Bind b
$c<$ :: forall a b. a -> Bind b -> Bind a
<$ :: forall a b. a -> Bind b -> Bind a
Functor, Int -> Bind name -> ShowS
[Bind name] -> ShowS
Bind name -> String
(Int -> Bind name -> ShowS)
-> (Bind name -> String)
-> ([Bind name] -> ShowS)
-> Show (Bind name)
forall name. Show name => Int -> Bind name -> ShowS
forall name. Show name => [Bind name] -> ShowS
forall name. Show name => Bind name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> Bind name -> ShowS
showsPrec :: Int -> Bind name -> ShowS
$cshow :: forall name. Show name => Bind name -> String
show :: Bind name -> String
$cshowList :: forall name. Show name => [Bind name] -> ShowS
showList :: [Bind name] -> ShowS
Show)
bindParams :: Bind name -> [Pattern name]
bindParams :: forall name. Bind name -> [Pattern name]
bindParams Bind name
b = case Bind name -> BindParams name
forall name. Bind name -> BindParams name
bParams Bind name
b of
PatternParams [Pattern name]
ps -> [Pattern name]
ps
DroppedParams Maybe Range
_ Int
_ -> []
dropParams :: BindParams name -> BindParams name
dropParams :: forall name. BindParams name -> BindParams name
dropParams BindParams name
bps = case BindParams name
bps of
PatternParams [Pattern name]
ps -> Maybe Range -> Int -> BindParams name
forall name. Maybe Range -> Int -> BindParams name
DroppedParams ([Pattern name] -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc [Pattern name]
ps) ([Pattern name] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Pattern name]
ps)
DroppedParams Maybe Range
rng Int
i -> Maybe Range -> Int -> BindParams name
forall name. Maybe Range -> Int -> BindParams name
DroppedParams Maybe Range
rng Int
i
bindHeaderLoc :: Bind name -> Maybe Range
Bind name
b = (Located name, (Maybe (Schema name), BindParams name))
-> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (Bind name -> Located name
forall name. Bind name -> Located name
bName Bind name
b, (Bind name -> Maybe (Schema name)
forall name. Bind name -> Maybe (Schema name)
bSignature Bind name
b, Bind name -> BindParams name
forall name. Bind name -> BindParams name
bParams Bind name
b))
noParams :: BindParams name
noParams :: forall name. BindParams name
noParams = [Pattern name] -> BindParams name
forall name. [Pattern name] -> BindParams name
PatternParams []
data BindParams name =
PatternParams [Pattern name]
| DroppedParams (Maybe Range) Int
deriving (BindParams name -> BindParams name -> Bool
(BindParams name -> BindParams name -> Bool)
-> (BindParams name -> BindParams name -> Bool)
-> Eq (BindParams name)
forall name. Eq name => BindParams name -> BindParams name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name. Eq name => BindParams name -> BindParams name -> Bool
== :: BindParams name -> BindParams name -> Bool
$c/= :: forall name. Eq name => BindParams name -> BindParams name -> Bool
/= :: BindParams name -> BindParams name -> Bool
Eq, (forall x. BindParams name -> Rep (BindParams name) x)
-> (forall x. Rep (BindParams name) x -> BindParams name)
-> Generic (BindParams name)
forall x. Rep (BindParams name) x -> BindParams name
forall x. BindParams name -> Rep (BindParams name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (BindParams name) x -> BindParams name
forall name x. BindParams name -> Rep (BindParams name) x
$cfrom :: forall name x. BindParams name -> Rep (BindParams name) x
from :: forall x. BindParams name -> Rep (BindParams name) x
$cto :: forall name x. Rep (BindParams name) x -> BindParams name
to :: forall x. Rep (BindParams name) x -> BindParams name
Generic, BindParams name -> ()
(BindParams name -> ()) -> NFData (BindParams name)
forall name. NFData name => BindParams name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => BindParams name -> ()
rnf :: BindParams name -> ()
NFData, (forall a b. (a -> b) -> BindParams a -> BindParams b)
-> (forall a b. a -> BindParams b -> BindParams a)
-> Functor BindParams
forall a b. a -> BindParams b -> BindParams a
forall a b. (a -> b) -> BindParams a -> BindParams b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> BindParams a -> BindParams b
fmap :: forall a b. (a -> b) -> BindParams a -> BindParams b
$c<$ :: forall a b. a -> BindParams b -> BindParams a
<$ :: forall a b. a -> BindParams b -> BindParams a
Functor, Int -> BindParams name -> ShowS
[BindParams name] -> ShowS
BindParams name -> String
(Int -> BindParams name -> ShowS)
-> (BindParams name -> String)
-> ([BindParams name] -> ShowS)
-> Show (BindParams name)
forall name. Show name => Int -> BindParams name -> ShowS
forall name. Show name => [BindParams name] -> ShowS
forall name. Show name => BindParams name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> BindParams name -> ShowS
showsPrec :: Int -> BindParams name -> ShowS
$cshow :: forall name. Show name => BindParams name -> String
show :: BindParams name -> String
$cshowList :: forall name. Show name => [BindParams name] -> ShowS
showList :: [BindParams name] -> ShowS
Show)
type LBindDef = Located (BindDef PName)
data BindDef name = DPrim
| DForeign (Maybe (BindImpl name))
| DImpl (BindImpl name)
deriving (BindDef name -> BindDef name -> Bool
(BindDef name -> BindDef name -> Bool)
-> (BindDef name -> BindDef name -> Bool) -> Eq (BindDef name)
forall name. Eq name => BindDef name -> BindDef name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name. Eq name => BindDef name -> BindDef name -> Bool
== :: BindDef name -> BindDef name -> Bool
$c/= :: forall name. Eq name => BindDef name -> BindDef name -> Bool
/= :: BindDef name -> BindDef name -> Bool
Eq, Int -> BindDef name -> ShowS
[BindDef name] -> ShowS
BindDef name -> String
(Int -> BindDef name -> ShowS)
-> (BindDef name -> String)
-> ([BindDef name] -> ShowS)
-> Show (BindDef name)
forall name. Show name => Int -> BindDef name -> ShowS
forall name. Show name => [BindDef name] -> ShowS
forall name. Show name => BindDef name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> BindDef name -> ShowS
showsPrec :: Int -> BindDef name -> ShowS
$cshow :: forall name. Show name => BindDef name -> String
show :: BindDef name -> String
$cshowList :: forall name. Show name => [BindDef name] -> ShowS
showList :: [BindDef name] -> ShowS
Show, (forall x. BindDef name -> Rep (BindDef name) x)
-> (forall x. Rep (BindDef name) x -> BindDef name)
-> Generic (BindDef name)
forall x. Rep (BindDef name) x -> BindDef name
forall x. BindDef name -> Rep (BindDef name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (BindDef name) x -> BindDef name
forall name x. BindDef name -> Rep (BindDef name) x
$cfrom :: forall name x. BindDef name -> Rep (BindDef name) x
from :: forall x. BindDef name -> Rep (BindDef name) x
$cto :: forall name x. Rep (BindDef name) x -> BindDef name
to :: forall x. Rep (BindDef name) x -> BindDef name
Generic, BindDef name -> ()
(BindDef name -> ()) -> NFData (BindDef name)
forall name. NFData name => BindDef name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => BindDef name -> ()
rnf :: BindDef name -> ()
NFData, (forall a b. (a -> b) -> BindDef a -> BindDef b)
-> (forall a b. a -> BindDef b -> BindDef a) -> Functor BindDef
forall a b. a -> BindDef b -> BindDef a
forall a b. (a -> b) -> BindDef a -> BindDef b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> BindDef a -> BindDef b
fmap :: forall a b. (a -> b) -> BindDef a -> BindDef b
$c<$ :: forall a b. a -> BindDef b -> BindDef a
<$ :: forall a b. a -> BindDef b -> BindDef a
Functor)
bindImpl :: Bind name -> Maybe (BindImpl name)
bindImpl :: forall name. Bind name -> Maybe (BindImpl name)
bindImpl Bind name
bind =
case Located (BindDef name) -> BindDef name
forall a. Located a -> a
thing (Bind name -> Located (BindDef name)
forall name. Bind name -> Located (BindDef name)
bDef Bind name
bind) of
BindDef name
DPrim -> Maybe (BindImpl name)
forall a. Maybe a
Nothing
DForeign Maybe (BindImpl name)
mi -> Maybe (BindImpl name)
mi
DImpl BindImpl name
i -> BindImpl name -> Maybe (BindImpl name)
forall a. a -> Maybe a
Just BindImpl name
i
data BindImpl name = DExpr (Expr name)
| DPropGuards [PropGuardCase name]
deriving (BindImpl name -> BindImpl name -> Bool
(BindImpl name -> BindImpl name -> Bool)
-> (BindImpl name -> BindImpl name -> Bool) -> Eq (BindImpl name)
forall name. Eq name => BindImpl name -> BindImpl name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name. Eq name => BindImpl name -> BindImpl name -> Bool
== :: BindImpl name -> BindImpl name -> Bool
$c/= :: forall name. Eq name => BindImpl name -> BindImpl name -> Bool
/= :: BindImpl name -> BindImpl name -> Bool
Eq, Int -> BindImpl name -> ShowS
[BindImpl name] -> ShowS
BindImpl name -> String
(Int -> BindImpl name -> ShowS)
-> (BindImpl name -> String)
-> ([BindImpl name] -> ShowS)
-> Show (BindImpl name)
forall name. Show name => Int -> BindImpl name -> ShowS
forall name. Show name => [BindImpl name] -> ShowS
forall name. Show name => BindImpl name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> BindImpl name -> ShowS
showsPrec :: Int -> BindImpl name -> ShowS
$cshow :: forall name. Show name => BindImpl name -> String
show :: BindImpl name -> String
$cshowList :: forall name. Show name => [BindImpl name] -> ShowS
showList :: [BindImpl name] -> ShowS
Show, (forall x. BindImpl name -> Rep (BindImpl name) x)
-> (forall x. Rep (BindImpl name) x -> BindImpl name)
-> Generic (BindImpl name)
forall x. Rep (BindImpl name) x -> BindImpl name
forall x. BindImpl name -> Rep (BindImpl name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (BindImpl name) x -> BindImpl name
forall name x. BindImpl name -> Rep (BindImpl name) x
$cfrom :: forall name x. BindImpl name -> Rep (BindImpl name) x
from :: forall x. BindImpl name -> Rep (BindImpl name) x
$cto :: forall name x. Rep (BindImpl name) x -> BindImpl name
to :: forall x. Rep (BindImpl name) x -> BindImpl name
Generic, BindImpl name -> ()
(BindImpl name -> ()) -> NFData (BindImpl name)
forall name. NFData name => BindImpl name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => BindImpl name -> ()
rnf :: BindImpl name -> ()
NFData, (forall a b. (a -> b) -> BindImpl a -> BindImpl b)
-> (forall a b. a -> BindImpl b -> BindImpl a) -> Functor BindImpl
forall a b. a -> BindImpl b -> BindImpl a
forall a b. (a -> b) -> BindImpl a -> BindImpl b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> BindImpl a -> BindImpl b
fmap :: forall a b. (a -> b) -> BindImpl a -> BindImpl b
$c<$ :: forall a b. a -> BindImpl b -> BindImpl a
<$ :: forall a b. a -> BindImpl b -> BindImpl a
Functor)
exprDef :: Expr name -> BindDef name
exprDef :: forall name. Expr name -> BindDef name
exprDef = BindImpl name -> BindDef name
forall name. BindImpl name -> BindDef name
DImpl (BindImpl name -> BindDef name)
-> (Expr name -> BindImpl name) -> Expr name -> BindDef name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr name -> BindImpl name
forall name. Expr name -> BindImpl name
DExpr
data PropGuardCase name = PropGuardCase
{ forall name. PropGuardCase name -> [Located (Prop name)]
pgcProps :: [Located (Prop name)]
, forall name. PropGuardCase name -> Expr name
pgcExpr :: Expr name
}
deriving (PropGuardCase name -> PropGuardCase name -> Bool
(PropGuardCase name -> PropGuardCase name -> Bool)
-> (PropGuardCase name -> PropGuardCase name -> Bool)
-> Eq (PropGuardCase name)
forall name.
Eq name =>
PropGuardCase name -> PropGuardCase name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name.
Eq name =>
PropGuardCase name -> PropGuardCase name -> Bool
== :: PropGuardCase name -> PropGuardCase name -> Bool
$c/= :: forall name.
Eq name =>
PropGuardCase name -> PropGuardCase name -> Bool
/= :: PropGuardCase name -> PropGuardCase name -> Bool
Eq,(forall x. PropGuardCase name -> Rep (PropGuardCase name) x)
-> (forall x. Rep (PropGuardCase name) x -> PropGuardCase name)
-> Generic (PropGuardCase name)
forall x. Rep (PropGuardCase name) x -> PropGuardCase name
forall x. PropGuardCase name -> Rep (PropGuardCase name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (PropGuardCase name) x -> PropGuardCase name
forall name x. PropGuardCase name -> Rep (PropGuardCase name) x
$cfrom :: forall name x. PropGuardCase name -> Rep (PropGuardCase name) x
from :: forall x. PropGuardCase name -> Rep (PropGuardCase name) x
$cto :: forall name x. Rep (PropGuardCase name) x -> PropGuardCase name
to :: forall x. Rep (PropGuardCase name) x -> PropGuardCase name
Generic,PropGuardCase name -> ()
(PropGuardCase name -> ()) -> NFData (PropGuardCase name)
forall name. NFData name => PropGuardCase name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => PropGuardCase name -> ()
rnf :: PropGuardCase name -> ()
NFData,(forall a b. (a -> b) -> PropGuardCase a -> PropGuardCase b)
-> (forall a b. a -> PropGuardCase b -> PropGuardCase a)
-> Functor PropGuardCase
forall a b. a -> PropGuardCase b -> PropGuardCase a
forall a b. (a -> b) -> PropGuardCase a -> PropGuardCase b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> PropGuardCase a -> PropGuardCase b
fmap :: forall a b. (a -> b) -> PropGuardCase a -> PropGuardCase b
$c<$ :: forall a b. a -> PropGuardCase b -> PropGuardCase a
<$ :: forall a b. a -> PropGuardCase b -> PropGuardCase a
Functor,Int -> PropGuardCase name -> ShowS
[PropGuardCase name] -> ShowS
PropGuardCase name -> String
(Int -> PropGuardCase name -> ShowS)
-> (PropGuardCase name -> String)
-> ([PropGuardCase name] -> ShowS)
-> Show (PropGuardCase name)
forall name. Show name => Int -> PropGuardCase name -> ShowS
forall name. Show name => [PropGuardCase name] -> ShowS
forall name. Show name => PropGuardCase name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> PropGuardCase name -> ShowS
showsPrec :: Int -> PropGuardCase name -> ShowS
$cshow :: forall name. Show name => PropGuardCase name -> String
show :: PropGuardCase name -> String
$cshowList :: forall name. Show name => [PropGuardCase name] -> ShowS
showList :: [PropGuardCase name] -> ShowS
Show)
data Pragma = PragmaNote String
| PragmaProperty
deriving (Pragma -> Pragma -> Bool
(Pragma -> Pragma -> Bool)
-> (Pragma -> Pragma -> Bool) -> Eq Pragma
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pragma -> Pragma -> Bool
== :: Pragma -> Pragma -> Bool
$c/= :: Pragma -> Pragma -> Bool
/= :: Pragma -> Pragma -> Bool
Eq, Int -> Pragma -> ShowS
[Pragma] -> ShowS
Pragma -> String
(Int -> Pragma -> ShowS)
-> (Pragma -> String) -> ([Pragma] -> ShowS) -> Show Pragma
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pragma -> ShowS
showsPrec :: Int -> Pragma -> ShowS
$cshow :: Pragma -> String
show :: Pragma -> String
$cshowList :: [Pragma] -> ShowS
showList :: [Pragma] -> ShowS
Show, (forall x. Pragma -> Rep Pragma x)
-> (forall x. Rep Pragma x -> Pragma) -> Generic Pragma
forall x. Rep Pragma x -> Pragma
forall x. Pragma -> Rep Pragma x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Pragma -> Rep Pragma x
from :: forall x. Pragma -> Rep Pragma x
$cto :: forall x. Rep Pragma x -> Pragma
to :: forall x. Rep Pragma x -> Pragma
Generic, Pragma -> ()
(Pragma -> ()) -> NFData Pragma
forall a. (a -> ()) -> NFData a
$crnf :: Pragma -> ()
rnf :: Pragma -> ()
NFData)
data Newtype name = Newtype
{ forall name. Newtype name -> Located name
nName :: Located name
, forall name. Newtype name -> [TParam name]
nParams :: [TParam name]
, forall name. Newtype name -> name
nConName :: !name
, forall name. Newtype name -> Rec (Type name)
nBody :: Rec (Type name)
} deriving (Newtype name -> Newtype name -> Bool
(Newtype name -> Newtype name -> Bool)
-> (Newtype name -> Newtype name -> Bool) -> Eq (Newtype name)
forall name. Eq name => Newtype name -> Newtype name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name. Eq name => Newtype name -> Newtype name -> Bool
== :: Newtype name -> Newtype name -> Bool
$c/= :: forall name. Eq name => Newtype name -> Newtype name -> Bool
/= :: Newtype name -> Newtype name -> Bool
Eq, Int -> Newtype name -> ShowS
[Newtype name] -> ShowS
Newtype name -> String
(Int -> Newtype name -> ShowS)
-> (Newtype name -> String)
-> ([Newtype name] -> ShowS)
-> Show (Newtype name)
forall name. Show name => Int -> Newtype name -> ShowS
forall name. Show name => [Newtype name] -> ShowS
forall name. Show name => Newtype name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> Newtype name -> ShowS
showsPrec :: Int -> Newtype name -> ShowS
$cshow :: forall name. Show name => Newtype name -> String
show :: Newtype name -> String
$cshowList :: forall name. Show name => [Newtype name] -> ShowS
showList :: [Newtype name] -> ShowS
Show, (forall x. Newtype name -> Rep (Newtype name) x)
-> (forall x. Rep (Newtype name) x -> Newtype name)
-> Generic (Newtype name)
forall x. Rep (Newtype name) x -> Newtype name
forall x. Newtype name -> Rep (Newtype name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (Newtype name) x -> Newtype name
forall name x. Newtype name -> Rep (Newtype name) x
$cfrom :: forall name x. Newtype name -> Rep (Newtype name) x
from :: forall x. Newtype name -> Rep (Newtype name) x
$cto :: forall name x. Rep (Newtype name) x -> Newtype name
to :: forall x. Rep (Newtype name) x -> Newtype name
Generic, Newtype name -> ()
(Newtype name -> ()) -> NFData (Newtype name)
forall name. NFData name => Newtype name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => Newtype name -> ()
rnf :: Newtype name -> ()
NFData)
data EnumDecl name = EnumDecl
{ forall name. EnumDecl name -> Located name
eName :: Located name
, forall name. EnumDecl name -> [TParam name]
eParams :: [TParam name]
, forall name. EnumDecl name -> [TopLevel (EnumCon name)]
eCons :: [TopLevel (EnumCon name)]
} deriving (Int -> EnumDecl name -> ShowS
[EnumDecl name] -> ShowS
EnumDecl name -> String
(Int -> EnumDecl name -> ShowS)
-> (EnumDecl name -> String)
-> ([EnumDecl name] -> ShowS)
-> Show (EnumDecl name)
forall name. Show name => Int -> EnumDecl name -> ShowS
forall name. Show name => [EnumDecl name] -> ShowS
forall name. Show name => EnumDecl name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> EnumDecl name -> ShowS
showsPrec :: Int -> EnumDecl name -> ShowS
$cshow :: forall name. Show name => EnumDecl name -> String
show :: EnumDecl name -> String
$cshowList :: forall name. Show name => [EnumDecl name] -> ShowS
showList :: [EnumDecl name] -> ShowS
Show, (forall x. EnumDecl name -> Rep (EnumDecl name) x)
-> (forall x. Rep (EnumDecl name) x -> EnumDecl name)
-> Generic (EnumDecl name)
forall x. Rep (EnumDecl name) x -> EnumDecl name
forall x. EnumDecl name -> Rep (EnumDecl name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (EnumDecl name) x -> EnumDecl name
forall name x. EnumDecl name -> Rep (EnumDecl name) x
$cfrom :: forall name x. EnumDecl name -> Rep (EnumDecl name) x
from :: forall x. EnumDecl name -> Rep (EnumDecl name) x
$cto :: forall name x. Rep (EnumDecl name) x -> EnumDecl name
to :: forall x. Rep (EnumDecl name) x -> EnumDecl name
Generic, EnumDecl name -> ()
(EnumDecl name -> ()) -> NFData (EnumDecl name)
forall name. NFData name => EnumDecl name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => EnumDecl name -> ()
rnf :: EnumDecl name -> ()
NFData)
data EnumCon name = EnumCon
{ forall name. EnumCon name -> Located name
ecName :: Located name
, forall name. EnumCon name -> [Type name]
ecFields :: [Type name]
} deriving (Int -> EnumCon name -> ShowS
[EnumCon name] -> ShowS
EnumCon name -> String
(Int -> EnumCon name -> ShowS)
-> (EnumCon name -> String)
-> ([EnumCon name] -> ShowS)
-> Show (EnumCon name)
forall name. Show name => Int -> EnumCon name -> ShowS
forall name. Show name => [EnumCon name] -> ShowS
forall name. Show name => EnumCon name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> EnumCon name -> ShowS
showsPrec :: Int -> EnumCon name -> ShowS
$cshow :: forall name. Show name => EnumCon name -> String
show :: EnumCon name -> String
$cshowList :: forall name. Show name => [EnumCon name] -> ShowS
showList :: [EnumCon name] -> ShowS
Show, (forall x. EnumCon name -> Rep (EnumCon name) x)
-> (forall x. Rep (EnumCon name) x -> EnumCon name)
-> Generic (EnumCon name)
forall x. Rep (EnumCon name) x -> EnumCon name
forall x. EnumCon name -> Rep (EnumCon name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (EnumCon name) x -> EnumCon name
forall name x. EnumCon name -> Rep (EnumCon name) x
$cfrom :: forall name x. EnumCon name -> Rep (EnumCon name) x
from :: forall x. EnumCon name -> Rep (EnumCon name) x
$cto :: forall name x. Rep (EnumCon name) x -> EnumCon name
to :: forall x. Rep (EnumCon name) x -> EnumCon name
Generic, EnumCon name -> ()
(EnumCon name -> ()) -> NFData (EnumCon name)
forall name. NFData name => EnumCon name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => EnumCon name -> ()
rnf :: EnumCon name -> ()
NFData)
data PrimType name = PrimType { forall name. PrimType name -> Located name
primTName :: Located name
, forall name. PrimType name -> Located Kind
primTKind :: Located Kind
, forall name. PrimType name -> ([TParam name], [Prop name])
primTCts :: ([TParam name], [Prop name])
, forall name. PrimType name -> Maybe Fixity
primTFixity :: Maybe Fixity
} deriving (Int -> PrimType name -> ShowS
[PrimType name] -> ShowS
PrimType name -> String
(Int -> PrimType name -> ShowS)
-> (PrimType name -> String)
-> ([PrimType name] -> ShowS)
-> Show (PrimType name)
forall name. Show name => Int -> PrimType name -> ShowS
forall name. Show name => [PrimType name] -> ShowS
forall name. Show name => PrimType name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> PrimType name -> ShowS
showsPrec :: Int -> PrimType name -> ShowS
$cshow :: forall name. Show name => PrimType name -> String
show :: PrimType name -> String
$cshowList :: forall name. Show name => [PrimType name] -> ShowS
showList :: [PrimType name] -> ShowS
Show,(forall x. PrimType name -> Rep (PrimType name) x)
-> (forall x. Rep (PrimType name) x -> PrimType name)
-> Generic (PrimType name)
forall x. Rep (PrimType name) x -> PrimType name
forall x. PrimType name -> Rep (PrimType name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (PrimType name) x -> PrimType name
forall name x. PrimType name -> Rep (PrimType name) x
$cfrom :: forall name x. PrimType name -> Rep (PrimType name) x
from :: forall x. PrimType name -> Rep (PrimType name) x
$cto :: forall name x. Rep (PrimType name) x -> PrimType name
to :: forall x. Rep (PrimType name) x -> PrimType name
Generic,PrimType name -> ()
(PrimType name -> ()) -> NFData (PrimType name)
forall name. NFData name => PrimType name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => PrimType name -> ()
rnf :: PrimType name -> ()
NFData)
data ReplInput name = ExprInput (Expr name)
| LetInput [Decl name]
| EmptyInput
deriving (ReplInput name -> ReplInput name -> Bool
(ReplInput name -> ReplInput name -> Bool)
-> (ReplInput name -> ReplInput name -> Bool)
-> Eq (ReplInput name)
forall name. Eq name => ReplInput name -> ReplInput name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name. Eq name => ReplInput name -> ReplInput name -> Bool
== :: ReplInput name -> ReplInput name -> Bool
$c/= :: forall name. Eq name => ReplInput name -> ReplInput name -> Bool
/= :: ReplInput name -> ReplInput name -> Bool
Eq, Int -> ReplInput name -> ShowS
[ReplInput name] -> ShowS
ReplInput name -> String
(Int -> ReplInput name -> ShowS)
-> (ReplInput name -> String)
-> ([ReplInput name] -> ShowS)
-> Show (ReplInput name)
forall name. Show name => Int -> ReplInput name -> ShowS
forall name. Show name => [ReplInput name] -> ShowS
forall name. Show name => ReplInput name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> ReplInput name -> ShowS
showsPrec :: Int -> ReplInput name -> ShowS
$cshow :: forall name. Show name => ReplInput name -> String
show :: ReplInput name -> String
$cshowList :: forall name. Show name => [ReplInput name] -> ShowS
showList :: [ReplInput name] -> ShowS
Show)
data ExportType = Public
| Private
deriving (ExportType -> ExportType -> Bool
(ExportType -> ExportType -> Bool)
-> (ExportType -> ExportType -> Bool) -> Eq ExportType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExportType -> ExportType -> Bool
== :: ExportType -> ExportType -> Bool
$c/= :: ExportType -> ExportType -> Bool
/= :: ExportType -> ExportType -> Bool
Eq, Int -> ExportType -> ShowS
[ExportType] -> ShowS
ExportType -> String
(Int -> ExportType -> ShowS)
-> (ExportType -> String)
-> ([ExportType] -> ShowS)
-> Show ExportType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExportType -> ShowS
showsPrec :: Int -> ExportType -> ShowS
$cshow :: ExportType -> String
show :: ExportType -> String
$cshowList :: [ExportType] -> ShowS
showList :: [ExportType] -> ShowS
Show, Eq ExportType
Eq ExportType =>
(ExportType -> ExportType -> Ordering)
-> (ExportType -> ExportType -> Bool)
-> (ExportType -> ExportType -> Bool)
-> (ExportType -> ExportType -> Bool)
-> (ExportType -> ExportType -> Bool)
-> (ExportType -> ExportType -> ExportType)
-> (ExportType -> ExportType -> ExportType)
-> Ord ExportType
ExportType -> ExportType -> Bool
ExportType -> ExportType -> Ordering
ExportType -> ExportType -> ExportType
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 :: ExportType -> ExportType -> Ordering
compare :: ExportType -> ExportType -> Ordering
$c< :: ExportType -> ExportType -> Bool
< :: ExportType -> ExportType -> Bool
$c<= :: ExportType -> ExportType -> Bool
<= :: ExportType -> ExportType -> Bool
$c> :: ExportType -> ExportType -> Bool
> :: ExportType -> ExportType -> Bool
$c>= :: ExportType -> ExportType -> Bool
>= :: ExportType -> ExportType -> Bool
$cmax :: ExportType -> ExportType -> ExportType
max :: ExportType -> ExportType -> ExportType
$cmin :: ExportType -> ExportType -> ExportType
min :: ExportType -> ExportType -> ExportType
Ord, (forall x. ExportType -> Rep ExportType x)
-> (forall x. Rep ExportType x -> ExportType) -> Generic ExportType
forall x. Rep ExportType x -> ExportType
forall x. ExportType -> Rep ExportType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExportType -> Rep ExportType x
from :: forall x. ExportType -> Rep ExportType x
$cto :: forall x. Rep ExportType x -> ExportType
to :: forall x. Rep ExportType x -> ExportType
Generic, ExportType -> ()
(ExportType -> ()) -> NFData ExportType
forall a. (a -> ()) -> NFData a
$crnf :: ExportType -> ()
rnf :: ExportType -> ()
NFData)
data TopLevel a = TopLevel { forall a. TopLevel a -> ExportType
tlExport :: ExportType
, forall a. TopLevel a -> Maybe (Located Text)
tlDoc :: Maybe (Located Text)
, forall a. TopLevel a -> a
tlValue :: a
}
deriving (Int -> TopLevel a -> ShowS
[TopLevel a] -> ShowS
TopLevel a -> String
(Int -> TopLevel a -> ShowS)
-> (TopLevel a -> String)
-> ([TopLevel a] -> ShowS)
-> Show (TopLevel a)
forall a. Show a => Int -> TopLevel a -> ShowS
forall a. Show a => [TopLevel a] -> ShowS
forall a. Show a => TopLevel a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> TopLevel a -> ShowS
showsPrec :: Int -> TopLevel a -> ShowS
$cshow :: forall a. Show a => TopLevel a -> String
show :: TopLevel a -> String
$cshowList :: forall a. Show a => [TopLevel a] -> ShowS
showList :: [TopLevel a] -> ShowS
Show, (forall x. TopLevel a -> Rep (TopLevel a) x)
-> (forall x. Rep (TopLevel a) x -> TopLevel a)
-> Generic (TopLevel a)
forall x. Rep (TopLevel a) x -> TopLevel a
forall x. TopLevel a -> Rep (TopLevel a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (TopLevel a) x -> TopLevel a
forall a x. TopLevel a -> Rep (TopLevel a) x
$cfrom :: forall a x. TopLevel a -> Rep (TopLevel a) x
from :: forall x. TopLevel a -> Rep (TopLevel a) x
$cto :: forall a x. Rep (TopLevel a) x -> TopLevel a
to :: forall x. Rep (TopLevel a) x -> TopLevel a
Generic, TopLevel a -> ()
(TopLevel a -> ()) -> NFData (TopLevel a)
forall a. NFData a => TopLevel a -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall a. NFData a => TopLevel a -> ()
rnf :: TopLevel a -> ()
NFData, (forall a b. (a -> b) -> TopLevel a -> TopLevel b)
-> (forall a b. a -> TopLevel b -> TopLevel a) -> Functor TopLevel
forall a b. a -> TopLevel b -> TopLevel a
forall a b. (a -> b) -> TopLevel a -> TopLevel b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> TopLevel a -> TopLevel b
fmap :: forall a b. (a -> b) -> TopLevel a -> TopLevel b
$c<$ :: forall a b. a -> TopLevel b -> TopLevel a
<$ :: forall a b. a -> TopLevel b -> TopLevel a
Functor, (forall m. Monoid m => TopLevel m -> m)
-> (forall m a. Monoid m => (a -> m) -> TopLevel a -> m)
-> (forall m a. Monoid m => (a -> m) -> TopLevel a -> m)
-> (forall a b. (a -> b -> b) -> b -> TopLevel a -> b)
-> (forall a b. (a -> b -> b) -> b -> TopLevel a -> b)
-> (forall b a. (b -> a -> b) -> b -> TopLevel a -> b)
-> (forall b a. (b -> a -> b) -> b -> TopLevel a -> b)
-> (forall a. (a -> a -> a) -> TopLevel a -> a)
-> (forall a. (a -> a -> a) -> TopLevel a -> a)
-> (forall a. TopLevel a -> [a])
-> (forall a. TopLevel a -> Bool)
-> (forall a. TopLevel a -> Int)
-> (forall a. Eq a => a -> TopLevel a -> Bool)
-> (forall a. Ord a => TopLevel a -> a)
-> (forall a. Ord a => TopLevel a -> a)
-> (forall a. Num a => TopLevel a -> a)
-> (forall a. Num a => TopLevel a -> a)
-> Foldable TopLevel
forall a. Eq a => a -> TopLevel a -> Bool
forall a. Num a => TopLevel a -> a
forall a. Ord a => TopLevel a -> a
forall m. Monoid m => TopLevel m -> m
forall a. TopLevel a -> Bool
forall a. TopLevel a -> Int
forall a. TopLevel a -> [a]
forall a. (a -> a -> a) -> TopLevel a -> a
forall m a. Monoid m => (a -> m) -> TopLevel a -> m
forall b a. (b -> a -> b) -> b -> TopLevel a -> b
forall a b. (a -> b -> b) -> b -> TopLevel a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => TopLevel m -> m
fold :: forall m. Monoid m => TopLevel m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> TopLevel a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> TopLevel a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> TopLevel a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> TopLevel a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> TopLevel a -> b
foldr :: forall a b. (a -> b -> b) -> b -> TopLevel a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> TopLevel a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> TopLevel a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> TopLevel a -> b
foldl :: forall b a. (b -> a -> b) -> b -> TopLevel a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> TopLevel a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> TopLevel a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> TopLevel a -> a
foldr1 :: forall a. (a -> a -> a) -> TopLevel a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> TopLevel a -> a
foldl1 :: forall a. (a -> a -> a) -> TopLevel a -> a
$ctoList :: forall a. TopLevel a -> [a]
toList :: forall a. TopLevel a -> [a]
$cnull :: forall a. TopLevel a -> Bool
null :: forall a. TopLevel a -> Bool
$clength :: forall a. TopLevel a -> Int
length :: forall a. TopLevel a -> Int
$celem :: forall a. Eq a => a -> TopLevel a -> Bool
elem :: forall a. Eq a => a -> TopLevel a -> Bool
$cmaximum :: forall a. Ord a => TopLevel a -> a
maximum :: forall a. Ord a => TopLevel a -> a
$cminimum :: forall a. Ord a => TopLevel a -> a
minimum :: forall a. Ord a => TopLevel a -> a
$csum :: forall a. Num a => TopLevel a -> a
sum :: forall a. Num a => TopLevel a -> a
$cproduct :: forall a. Num a => TopLevel a -> a
product :: forall a. Num a => TopLevel a -> a
Foldable, Functor TopLevel
Foldable TopLevel
(Functor TopLevel, Foldable TopLevel) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TopLevel a -> f (TopLevel b))
-> (forall (f :: * -> *) a.
Applicative f =>
TopLevel (f a) -> f (TopLevel a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TopLevel a -> m (TopLevel b))
-> (forall (m :: * -> *) a.
Monad m =>
TopLevel (m a) -> m (TopLevel a))
-> Traversable TopLevel
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => TopLevel (m a) -> m (TopLevel a)
forall (f :: * -> *) a.
Applicative f =>
TopLevel (f a) -> f (TopLevel a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TopLevel a -> m (TopLevel b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TopLevel a -> f (TopLevel b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TopLevel a -> f (TopLevel b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TopLevel a -> f (TopLevel b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
TopLevel (f a) -> f (TopLevel a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
TopLevel (f a) -> f (TopLevel a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TopLevel a -> m (TopLevel b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TopLevel a -> m (TopLevel b)
$csequence :: forall (m :: * -> *) a. Monad m => TopLevel (m a) -> m (TopLevel a)
sequence :: forall (m :: * -> *) a. Monad m => TopLevel (m a) -> m (TopLevel a)
Traversable)
data NumInfo = BinLit Text Int
| OctLit Text Int
| DecLit Text
| HexLit Text Int
| PolyLit Int
deriving (NumInfo -> NumInfo -> Bool
(NumInfo -> NumInfo -> Bool)
-> (NumInfo -> NumInfo -> Bool) -> Eq NumInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NumInfo -> NumInfo -> Bool
== :: NumInfo -> NumInfo -> Bool
$c/= :: NumInfo -> NumInfo -> Bool
/= :: NumInfo -> NumInfo -> Bool
Eq, Int -> NumInfo -> ShowS
[NumInfo] -> ShowS
NumInfo -> String
(Int -> NumInfo -> ShowS)
-> (NumInfo -> String) -> ([NumInfo] -> ShowS) -> Show NumInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NumInfo -> ShowS
showsPrec :: Int -> NumInfo -> ShowS
$cshow :: NumInfo -> String
show :: NumInfo -> String
$cshowList :: [NumInfo] -> ShowS
showList :: [NumInfo] -> ShowS
Show, (forall x. NumInfo -> Rep NumInfo x)
-> (forall x. Rep NumInfo x -> NumInfo) -> Generic NumInfo
forall x. Rep NumInfo x -> NumInfo
forall x. NumInfo -> Rep NumInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NumInfo -> Rep NumInfo x
from :: forall x. NumInfo -> Rep NumInfo x
$cto :: forall x. Rep NumInfo x -> NumInfo
to :: forall x. Rep NumInfo x -> NumInfo
Generic, NumInfo -> ()
(NumInfo -> ()) -> NFData NumInfo
forall a. (a -> ()) -> NFData a
$crnf :: NumInfo -> ()
rnf :: NumInfo -> ()
NFData)
data FracInfo = BinFrac Text
| OctFrac Text
| DecFrac Text
| HexFrac Text
deriving (FracInfo -> FracInfo -> Bool
(FracInfo -> FracInfo -> Bool)
-> (FracInfo -> FracInfo -> Bool) -> Eq FracInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FracInfo -> FracInfo -> Bool
== :: FracInfo -> FracInfo -> Bool
$c/= :: FracInfo -> FracInfo -> Bool
/= :: FracInfo -> FracInfo -> Bool
Eq,Int -> FracInfo -> ShowS
[FracInfo] -> ShowS
FracInfo -> String
(Int -> FracInfo -> ShowS)
-> (FracInfo -> String) -> ([FracInfo] -> ShowS) -> Show FracInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FracInfo -> ShowS
showsPrec :: Int -> FracInfo -> ShowS
$cshow :: FracInfo -> String
show :: FracInfo -> String
$cshowList :: [FracInfo] -> ShowS
showList :: [FracInfo] -> ShowS
Show,(forall x. FracInfo -> Rep FracInfo x)
-> (forall x. Rep FracInfo x -> FracInfo) -> Generic FracInfo
forall x. Rep FracInfo x -> FracInfo
forall x. FracInfo -> Rep FracInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FracInfo -> Rep FracInfo x
from :: forall x. FracInfo -> Rep FracInfo x
$cto :: forall x. Rep FracInfo x -> FracInfo
to :: forall x. Rep FracInfo x -> FracInfo
Generic,FracInfo -> ()
(FracInfo -> ()) -> NFData FracInfo
forall a. (a -> ()) -> NFData a
$crnf :: FracInfo -> ()
rnf :: FracInfo -> ()
NFData)
data Literal = ECNum Integer NumInfo
| ECChar Char
| ECFrac Rational FracInfo
| ECString 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, 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, (forall x. Literal -> Rep Literal x)
-> (forall x. Rep Literal x -> Literal) -> Generic Literal
forall x. Rep Literal x -> Literal
forall x. Literal -> Rep Literal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Literal -> Rep Literal x
from :: forall x. Literal -> Rep Literal x
$cto :: forall x. Rep Literal x -> Literal
to :: forall x. Rep Literal x -> Literal
Generic, Literal -> ()
(Literal -> ()) -> NFData Literal
forall a. (a -> ()) -> NFData a
$crnf :: Literal -> ()
rnf :: Literal -> ()
NFData)
data Expr n = EVar n
| ELit Literal
| EGenerate (Expr n)
| ETuple [Expr n]
| ERecord (Rec (Expr n))
| ESel (Expr n) Selector
| EUpd (Maybe (Expr n)) [ UpdField n ]
| EList [Expr n]
| EFromTo (Type n) (Maybe (Type n)) (Type n) (Maybe (Type n))
| EFromToBy Bool (Type n) (Type n) (Type n) (Maybe (Type n))
| EFromToDownBy Bool (Type n) (Type n) (Type n) (Maybe (Type n))
| EFromToLessThan (Type n) (Type n) (Maybe (Type n))
| EInfFrom (Expr n) (Maybe (Expr n))
| EComp (Expr n) [[Match n]]
| EApp (Expr n) (Expr n)
| EAppT (Expr n) [(TypeInst n)]
| EIf (Expr n) (Expr n) (Expr n)
| ECase (Expr n) [CaseAlt n]
| EWhere (Expr n) [Decl n]
| ETyped (Expr n) (Type n)
| ETypeVal (Type n)
| EFun (FunDesc n) [Pattern n] (Expr n)
| ELocated (Expr n) Range
| ESplit (Expr n)
| EParens (Expr n)
| EInfix (Expr n) (Located n) Fixity (Expr n)
| EPrefix PrefixOp (Expr n)
deriving (Expr n -> Expr n -> Bool
(Expr n -> Expr n -> Bool)
-> (Expr n -> Expr n -> Bool) -> Eq (Expr n)
forall n. Eq n => Expr n -> Expr n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n. Eq n => Expr n -> Expr n -> Bool
== :: Expr n -> Expr n -> Bool
$c/= :: forall n. Eq n => Expr n -> Expr n -> Bool
/= :: Expr n -> Expr n -> Bool
Eq, Int -> Expr n -> ShowS
[Expr n] -> ShowS
Expr n -> String
(Int -> Expr n -> ShowS)
-> (Expr n -> String) -> ([Expr n] -> ShowS) -> Show (Expr n)
forall n. Show n => Int -> Expr n -> ShowS
forall n. Show n => [Expr n] -> ShowS
forall n. Show n => Expr n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> Expr n -> ShowS
showsPrec :: Int -> Expr n -> ShowS
$cshow :: forall n. Show n => Expr n -> String
show :: Expr n -> String
$cshowList :: forall n. Show n => [Expr n] -> ShowS
showList :: [Expr n] -> ShowS
Show, (forall x. Expr n -> Rep (Expr n) x)
-> (forall x. Rep (Expr n) x -> Expr n) -> Generic (Expr n)
forall x. Rep (Expr n) x -> Expr n
forall x. Expr n -> Rep (Expr n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (Expr n) x -> Expr n
forall n x. Expr n -> Rep (Expr n) x
$cfrom :: forall n x. Expr n -> Rep (Expr n) x
from :: forall x. Expr n -> Rep (Expr n) x
$cto :: forall n x. Rep (Expr n) x -> Expr n
to :: forall x. Rep (Expr n) x -> Expr n
Generic, Expr n -> ()
(Expr n -> ()) -> NFData (Expr n)
forall n. NFData n => Expr n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => Expr n -> ()
rnf :: Expr n -> ()
NFData, (forall a b. (a -> b) -> Expr a -> Expr b)
-> (forall a b. a -> Expr b -> Expr a) -> Functor Expr
forall a b. a -> Expr b -> Expr a
forall a b. (a -> b) -> Expr a -> Expr b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Expr a -> Expr b
fmap :: forall a b. (a -> b) -> Expr a -> Expr b
$c<$ :: forall a b. a -> Expr b -> Expr a
<$ :: forall a b. a -> Expr b -> Expr a
Functor)
data PrefixOp = PrefixNeg
| PrefixComplement
deriving (PrefixOp -> PrefixOp -> Bool
(PrefixOp -> PrefixOp -> Bool)
-> (PrefixOp -> PrefixOp -> Bool) -> Eq PrefixOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PrefixOp -> PrefixOp -> Bool
== :: PrefixOp -> PrefixOp -> Bool
$c/= :: PrefixOp -> PrefixOp -> Bool
/= :: PrefixOp -> PrefixOp -> Bool
Eq, Int -> PrefixOp -> ShowS
[PrefixOp] -> ShowS
PrefixOp -> String
(Int -> PrefixOp -> ShowS)
-> (PrefixOp -> String) -> ([PrefixOp] -> ShowS) -> Show PrefixOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrefixOp -> ShowS
showsPrec :: Int -> PrefixOp -> ShowS
$cshow :: PrefixOp -> String
show :: PrefixOp -> String
$cshowList :: [PrefixOp] -> ShowS
showList :: [PrefixOp] -> ShowS
Show, (forall x. PrefixOp -> Rep PrefixOp x)
-> (forall x. Rep PrefixOp x -> PrefixOp) -> Generic PrefixOp
forall x. Rep PrefixOp x -> PrefixOp
forall x. PrefixOp -> Rep PrefixOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PrefixOp -> Rep PrefixOp x
from :: forall x. PrefixOp -> Rep PrefixOp x
$cto :: forall x. Rep PrefixOp x -> PrefixOp
to :: forall x. Rep PrefixOp x -> PrefixOp
Generic, PrefixOp -> ()
(PrefixOp -> ()) -> NFData PrefixOp
forall a. (a -> ()) -> NFData a
$crnf :: PrefixOp -> ()
rnf :: PrefixOp -> ()
NFData)
prefixFixity :: PrefixOp -> Fixity
prefixFixity :: PrefixOp -> Fixity
prefixFixity PrefixOp
op = Fixity { fAssoc :: Assoc
fAssoc = Assoc
LeftAssoc, Int
fLevel :: Int
fLevel :: Int
.. }
where fLevel :: Int
fLevel = case PrefixOp
op of
PrefixOp
PrefixNeg -> Int
80
PrefixOp
PrefixComplement -> Int
100
data FunDesc n =
FunDesc
{ forall n. FunDesc n -> Maybe n
funDescrName :: Maybe n
, forall n. FunDesc n -> Int
funDescrArgOffset :: Int
}
deriving (FunDesc n -> FunDesc n -> Bool
(FunDesc n -> FunDesc n -> Bool)
-> (FunDesc n -> FunDesc n -> Bool) -> Eq (FunDesc n)
forall n. Eq n => FunDesc n -> FunDesc n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n. Eq n => FunDesc n -> FunDesc n -> Bool
== :: FunDesc n -> FunDesc n -> Bool
$c/= :: forall n. Eq n => FunDesc n -> FunDesc n -> Bool
/= :: FunDesc n -> FunDesc n -> Bool
Eq, Int -> FunDesc n -> ShowS
[FunDesc n] -> ShowS
FunDesc n -> String
(Int -> FunDesc n -> ShowS)
-> (FunDesc n -> String)
-> ([FunDesc n] -> ShowS)
-> Show (FunDesc n)
forall n. Show n => Int -> FunDesc n -> ShowS
forall n. Show n => [FunDesc n] -> ShowS
forall n. Show n => FunDesc n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> FunDesc n -> ShowS
showsPrec :: Int -> FunDesc n -> ShowS
$cshow :: forall n. Show n => FunDesc n -> String
show :: FunDesc n -> String
$cshowList :: forall n. Show n => [FunDesc n] -> ShowS
showList :: [FunDesc n] -> ShowS
Show, (forall x. FunDesc n -> Rep (FunDesc n) x)
-> (forall x. Rep (FunDesc n) x -> FunDesc n)
-> Generic (FunDesc n)
forall x. Rep (FunDesc n) x -> FunDesc n
forall x. FunDesc n -> Rep (FunDesc n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (FunDesc n) x -> FunDesc n
forall n x. FunDesc n -> Rep (FunDesc n) x
$cfrom :: forall n x. FunDesc n -> Rep (FunDesc n) x
from :: forall x. FunDesc n -> Rep (FunDesc n) x
$cto :: forall n x. Rep (FunDesc n) x -> FunDesc n
to :: forall x. Rep (FunDesc n) x -> FunDesc n
Generic, FunDesc n -> ()
(FunDesc n -> ()) -> NFData (FunDesc n)
forall n. NFData n => FunDesc n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => FunDesc n -> ()
rnf :: FunDesc n -> ()
NFData, (forall a b. (a -> b) -> FunDesc a -> FunDesc b)
-> (forall a b. a -> FunDesc b -> FunDesc a) -> Functor FunDesc
forall a b. a -> FunDesc b -> FunDesc a
forall a b. (a -> b) -> FunDesc a -> FunDesc b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> FunDesc a -> FunDesc b
fmap :: forall a b. (a -> b) -> FunDesc a -> FunDesc b
$c<$ :: forall a b. a -> FunDesc b -> FunDesc a
<$ :: forall a b. a -> FunDesc b -> FunDesc a
Functor)
emptyFunDesc :: FunDesc n
emptyFunDesc :: forall n. FunDesc n
emptyFunDesc = Maybe n -> Int -> FunDesc n
forall n. Maybe n -> Int -> FunDesc n
FunDesc Maybe n
forall a. Maybe a
Nothing Int
0
data UpdField n = UpdField UpdHow [Located Selector] (Expr n)
deriving (UpdField n -> UpdField n -> Bool
(UpdField n -> UpdField n -> Bool)
-> (UpdField n -> UpdField n -> Bool) -> Eq (UpdField n)
forall n. Eq n => UpdField n -> UpdField n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n. Eq n => UpdField n -> UpdField n -> Bool
== :: UpdField n -> UpdField n -> Bool
$c/= :: forall n. Eq n => UpdField n -> UpdField n -> Bool
/= :: UpdField n -> UpdField n -> Bool
Eq, Int -> UpdField n -> ShowS
[UpdField n] -> ShowS
UpdField n -> String
(Int -> UpdField n -> ShowS)
-> (UpdField n -> String)
-> ([UpdField n] -> ShowS)
-> Show (UpdField n)
forall n. Show n => Int -> UpdField n -> ShowS
forall n. Show n => [UpdField n] -> ShowS
forall n. Show n => UpdField n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> UpdField n -> ShowS
showsPrec :: Int -> UpdField n -> ShowS
$cshow :: forall n. Show n => UpdField n -> String
show :: UpdField n -> String
$cshowList :: forall n. Show n => [UpdField n] -> ShowS
showList :: [UpdField n] -> ShowS
Show, (forall x. UpdField n -> Rep (UpdField n) x)
-> (forall x. Rep (UpdField n) x -> UpdField n)
-> Generic (UpdField n)
forall x. Rep (UpdField n) x -> UpdField n
forall x. UpdField n -> Rep (UpdField n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (UpdField n) x -> UpdField n
forall n x. UpdField n -> Rep (UpdField n) x
$cfrom :: forall n x. UpdField n -> Rep (UpdField n) x
from :: forall x. UpdField n -> Rep (UpdField n) x
$cto :: forall n x. Rep (UpdField n) x -> UpdField n
to :: forall x. Rep (UpdField n) x -> UpdField n
Generic, UpdField n -> ()
(UpdField n -> ()) -> NFData (UpdField n)
forall n. NFData n => UpdField n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => UpdField n -> ()
rnf :: UpdField n -> ()
NFData, (forall a b. (a -> b) -> UpdField a -> UpdField b)
-> (forall a b. a -> UpdField b -> UpdField a) -> Functor UpdField
forall a b. a -> UpdField b -> UpdField a
forall a b. (a -> b) -> UpdField a -> UpdField b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> UpdField a -> UpdField b
fmap :: forall a b. (a -> b) -> UpdField a -> UpdField b
$c<$ :: forall a b. a -> UpdField b -> UpdField a
<$ :: forall a b. a -> UpdField b -> UpdField a
Functor)
data UpdHow = UpdSet | UpdFun
deriving (UpdHow -> UpdHow -> Bool
(UpdHow -> UpdHow -> Bool)
-> (UpdHow -> UpdHow -> Bool) -> Eq UpdHow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpdHow -> UpdHow -> Bool
== :: UpdHow -> UpdHow -> Bool
$c/= :: UpdHow -> UpdHow -> Bool
/= :: UpdHow -> UpdHow -> Bool
Eq, Int -> UpdHow -> ShowS
[UpdHow] -> ShowS
UpdHow -> String
(Int -> UpdHow -> ShowS)
-> (UpdHow -> String) -> ([UpdHow] -> ShowS) -> Show UpdHow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UpdHow -> ShowS
showsPrec :: Int -> UpdHow -> ShowS
$cshow :: UpdHow -> String
show :: UpdHow -> String
$cshowList :: [UpdHow] -> ShowS
showList :: [UpdHow] -> ShowS
Show, (forall x. UpdHow -> Rep UpdHow x)
-> (forall x. Rep UpdHow x -> UpdHow) -> Generic UpdHow
forall x. Rep UpdHow x -> UpdHow
forall x. UpdHow -> Rep UpdHow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UpdHow -> Rep UpdHow x
from :: forall x. UpdHow -> Rep UpdHow x
$cto :: forall x. Rep UpdHow x -> UpdHow
to :: forall x. Rep UpdHow x -> UpdHow
Generic, UpdHow -> ()
(UpdHow -> ()) -> NFData UpdHow
forall a. (a -> ()) -> NFData a
$crnf :: UpdHow -> ()
rnf :: UpdHow -> ()
NFData)
data TypeInst name = NamedInst (Named (Type name))
| PosInst (Type name)
deriving (TypeInst name -> TypeInst name -> Bool
(TypeInst name -> TypeInst name -> Bool)
-> (TypeInst name -> TypeInst name -> Bool) -> Eq (TypeInst name)
forall name. Eq name => TypeInst name -> TypeInst name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name. Eq name => TypeInst name -> TypeInst name -> Bool
== :: TypeInst name -> TypeInst name -> Bool
$c/= :: forall name. Eq name => TypeInst name -> TypeInst name -> Bool
/= :: TypeInst name -> TypeInst name -> Bool
Eq, Int -> TypeInst name -> ShowS
[TypeInst name] -> ShowS
TypeInst name -> String
(Int -> TypeInst name -> ShowS)
-> (TypeInst name -> String)
-> ([TypeInst name] -> ShowS)
-> Show (TypeInst name)
forall name. Show name => Int -> TypeInst name -> ShowS
forall name. Show name => [TypeInst name] -> ShowS
forall name. Show name => TypeInst name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> TypeInst name -> ShowS
showsPrec :: Int -> TypeInst name -> ShowS
$cshow :: forall name. Show name => TypeInst name -> String
show :: TypeInst name -> String
$cshowList :: forall name. Show name => [TypeInst name] -> ShowS
showList :: [TypeInst name] -> ShowS
Show, (forall x. TypeInst name -> Rep (TypeInst name) x)
-> (forall x. Rep (TypeInst name) x -> TypeInst name)
-> Generic (TypeInst name)
forall x. Rep (TypeInst name) x -> TypeInst name
forall x. TypeInst name -> Rep (TypeInst name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (TypeInst name) x -> TypeInst name
forall name x. TypeInst name -> Rep (TypeInst name) x
$cfrom :: forall name x. TypeInst name -> Rep (TypeInst name) x
from :: forall x. TypeInst name -> Rep (TypeInst name) x
$cto :: forall name x. Rep (TypeInst name) x -> TypeInst name
to :: forall x. Rep (TypeInst name) x -> TypeInst name
Generic, TypeInst name -> ()
(TypeInst name -> ()) -> NFData (TypeInst name)
forall name. NFData name => TypeInst name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => TypeInst name -> ()
rnf :: TypeInst name -> ()
NFData, (forall a b. (a -> b) -> TypeInst a -> TypeInst b)
-> (forall a b. a -> TypeInst b -> TypeInst a) -> Functor TypeInst
forall a b. a -> TypeInst b -> TypeInst a
forall a b. (a -> b) -> TypeInst a -> TypeInst b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> TypeInst a -> TypeInst b
fmap :: forall a b. (a -> b) -> TypeInst a -> TypeInst b
$c<$ :: forall a b. a -> TypeInst b -> TypeInst a
<$ :: forall a b. a -> TypeInst b -> TypeInst a
Functor)
data Match name = Match (Pattern name) (Expr name)
| MatchLet (Bind name)
deriving (Match name -> Match name -> Bool
(Match name -> Match name -> Bool)
-> (Match name -> Match name -> Bool) -> Eq (Match name)
forall name. Eq name => Match name -> Match name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall name. Eq name => Match name -> Match name -> Bool
== :: Match name -> Match name -> Bool
$c/= :: forall name. Eq name => Match name -> Match name -> Bool
/= :: Match name -> Match name -> Bool
Eq, Int -> Match name -> ShowS
[Match name] -> ShowS
Match name -> String
(Int -> Match name -> ShowS)
-> (Match name -> String)
-> ([Match name] -> ShowS)
-> Show (Match name)
forall name. Show name => Int -> Match name -> ShowS
forall name. Show name => [Match name] -> ShowS
forall name. Show name => Match name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall name. Show name => Int -> Match name -> ShowS
showsPrec :: Int -> Match name -> ShowS
$cshow :: forall name. Show name => Match name -> String
show :: Match name -> String
$cshowList :: forall name. Show name => [Match name] -> ShowS
showList :: [Match name] -> ShowS
Show, (forall x. Match name -> Rep (Match name) x)
-> (forall x. Rep (Match name) x -> Match name)
-> Generic (Match name)
forall x. Rep (Match name) x -> Match name
forall x. Match name -> Rep (Match name) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall name x. Rep (Match name) x -> Match name
forall name x. Match name -> Rep (Match name) x
$cfrom :: forall name x. Match name -> Rep (Match name) x
from :: forall x. Match name -> Rep (Match name) x
$cto :: forall name x. Rep (Match name) x -> Match name
to :: forall x. Rep (Match name) x -> Match name
Generic, Match name -> ()
(Match name -> ()) -> NFData (Match name)
forall name. NFData name => Match name -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall name. NFData name => Match name -> ()
rnf :: Match name -> ()
NFData, (forall a b. (a -> b) -> Match a -> Match b)
-> (forall a b. a -> Match b -> Match a) -> Functor Match
forall a b. a -> Match b -> Match a
forall a b. (a -> b) -> Match a -> Match b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Match a -> Match b
fmap :: forall a b. (a -> b) -> Match a -> Match b
$c<$ :: forall a b. a -> Match b -> Match a
<$ :: forall a b. a -> Match b -> Match a
Functor)
data Pattern n = PVar (Located n)
| PWild
| PTuple [Pattern n]
| PRecord (Rec (Pattern n))
| PList [ Pattern n ]
| PTyped (Pattern n) (Type n)
| PSplit (Pattern n) (Pattern n)
| PCon (Located n) [Pattern n]
| PLocated (Pattern n) Range
deriving (Pattern n -> Pattern n -> Bool
(Pattern n -> Pattern n -> Bool)
-> (Pattern n -> Pattern n -> Bool) -> Eq (Pattern n)
forall n. Eq n => Pattern n -> Pattern n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n. Eq n => Pattern n -> Pattern n -> Bool
== :: Pattern n -> Pattern n -> Bool
$c/= :: forall n. Eq n => Pattern n -> Pattern n -> Bool
/= :: Pattern n -> Pattern n -> Bool
Eq, Int -> Pattern n -> ShowS
[Pattern n] -> ShowS
Pattern n -> String
(Int -> Pattern n -> ShowS)
-> (Pattern n -> String)
-> ([Pattern n] -> ShowS)
-> Show (Pattern n)
forall n. Show n => Int -> Pattern n -> ShowS
forall n. Show n => [Pattern n] -> ShowS
forall n. Show n => Pattern n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> Pattern n -> ShowS
showsPrec :: Int -> Pattern n -> ShowS
$cshow :: forall n. Show n => Pattern n -> String
show :: Pattern n -> String
$cshowList :: forall n. Show n => [Pattern n] -> ShowS
showList :: [Pattern n] -> ShowS
Show, (forall x. Pattern n -> Rep (Pattern n) x)
-> (forall x. Rep (Pattern n) x -> Pattern n)
-> Generic (Pattern n)
forall x. Rep (Pattern n) x -> Pattern n
forall x. Pattern n -> Rep (Pattern n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (Pattern n) x -> Pattern n
forall n x. Pattern n -> Rep (Pattern n) x
$cfrom :: forall n x. Pattern n -> Rep (Pattern n) x
from :: forall x. Pattern n -> Rep (Pattern n) x
$cto :: forall n x. Rep (Pattern n) x -> Pattern n
to :: forall x. Rep (Pattern n) x -> Pattern n
Generic, Pattern n -> ()
(Pattern n -> ()) -> NFData (Pattern n)
forall n. NFData n => Pattern n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => Pattern n -> ()
rnf :: Pattern n -> ()
NFData, (forall a b. (a -> b) -> Pattern a -> Pattern b)
-> (forall a b. a -> Pattern b -> Pattern a) -> Functor Pattern
forall a b. a -> Pattern b -> Pattern a
forall a b. (a -> b) -> Pattern a -> Pattern b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Pattern a -> Pattern b
fmap :: forall a b. (a -> b) -> Pattern a -> Pattern b
$c<$ :: forall a b. a -> Pattern b -> Pattern a
<$ :: forall a b. a -> Pattern b -> Pattern a
Functor)
data CaseAlt n = CaseAlt (Pattern n) (Expr n)
deriving (CaseAlt n -> CaseAlt n -> Bool
(CaseAlt n -> CaseAlt n -> Bool)
-> (CaseAlt n -> CaseAlt n -> Bool) -> Eq (CaseAlt n)
forall n. Eq n => CaseAlt n -> CaseAlt n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n. Eq n => CaseAlt n -> CaseAlt n -> Bool
== :: CaseAlt n -> CaseAlt n -> Bool
$c/= :: forall n. Eq n => CaseAlt n -> CaseAlt n -> Bool
/= :: CaseAlt n -> CaseAlt n -> Bool
Eq, Int -> CaseAlt n -> ShowS
[CaseAlt n] -> ShowS
CaseAlt n -> String
(Int -> CaseAlt n -> ShowS)
-> (CaseAlt n -> String)
-> ([CaseAlt n] -> ShowS)
-> Show (CaseAlt n)
forall n. Show n => Int -> CaseAlt n -> ShowS
forall n. Show n => [CaseAlt n] -> ShowS
forall n. Show n => CaseAlt n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> CaseAlt n -> ShowS
showsPrec :: Int -> CaseAlt n -> ShowS
$cshow :: forall n. Show n => CaseAlt n -> String
show :: CaseAlt n -> String
$cshowList :: forall n. Show n => [CaseAlt n] -> ShowS
showList :: [CaseAlt n] -> ShowS
Show, (forall x. CaseAlt n -> Rep (CaseAlt n) x)
-> (forall x. Rep (CaseAlt n) x -> CaseAlt n)
-> Generic (CaseAlt n)
forall x. Rep (CaseAlt n) x -> CaseAlt n
forall x. CaseAlt n -> Rep (CaseAlt n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (CaseAlt n) x -> CaseAlt n
forall n x. CaseAlt n -> Rep (CaseAlt n) x
$cfrom :: forall n x. CaseAlt n -> Rep (CaseAlt n) x
from :: forall x. CaseAlt n -> Rep (CaseAlt n) x
$cto :: forall n x. Rep (CaseAlt n) x -> CaseAlt n
to :: forall x. Rep (CaseAlt n) x -> CaseAlt n
Generic, CaseAlt n -> ()
(CaseAlt n -> ()) -> NFData (CaseAlt n)
forall n. NFData n => CaseAlt n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => CaseAlt n -> ()
rnf :: CaseAlt n -> ()
NFData, (forall a b. (a -> b) -> CaseAlt a -> CaseAlt b)
-> (forall a b. a -> CaseAlt b -> CaseAlt a) -> Functor CaseAlt
forall a b. a -> CaseAlt b -> CaseAlt a
forall a b. (a -> b) -> CaseAlt a -> CaseAlt b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> CaseAlt a -> CaseAlt b
fmap :: forall a b. (a -> b) -> CaseAlt a -> CaseAlt b
$c<$ :: forall a b. a -> CaseAlt b -> CaseAlt a
<$ :: forall a b. a -> CaseAlt b -> CaseAlt a
Functor)
data Named a = Named { forall a. Named a -> Located Ident
name :: Located Ident, forall a. Named a -> a
value :: a }
deriving (Named a -> Named a -> Bool
(Named a -> Named a -> Bool)
-> (Named a -> Named a -> Bool) -> Eq (Named a)
forall a. Eq a => Named a -> Named a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Named a -> Named a -> Bool
== :: Named a -> Named a -> Bool
$c/= :: forall a. Eq a => Named a -> Named a -> Bool
/= :: Named a -> Named a -> Bool
Eq, Int -> Named a -> ShowS
[Named a] -> ShowS
Named a -> String
(Int -> Named a -> ShowS)
-> (Named a -> String) -> ([Named a] -> ShowS) -> Show (Named a)
forall a. Show a => Int -> Named a -> ShowS
forall a. Show a => [Named a] -> ShowS
forall a. Show a => Named a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Named a -> ShowS
showsPrec :: Int -> Named a -> ShowS
$cshow :: forall a. Show a => Named a -> String
show :: Named a -> String
$cshowList :: forall a. Show a => [Named a] -> ShowS
showList :: [Named a] -> ShowS
Show, (forall m. Monoid m => Named m -> m)
-> (forall m a. Monoid m => (a -> m) -> Named a -> m)
-> (forall m a. Monoid m => (a -> m) -> Named a -> m)
-> (forall a b. (a -> b -> b) -> b -> Named a -> b)
-> (forall a b. (a -> b -> b) -> b -> Named a -> b)
-> (forall b a. (b -> a -> b) -> b -> Named a -> b)
-> (forall b a. (b -> a -> b) -> b -> Named a -> b)
-> (forall a. (a -> a -> a) -> Named a -> a)
-> (forall a. (a -> a -> a) -> Named a -> a)
-> (forall a. Named a -> [a])
-> (forall a. Named a -> Bool)
-> (forall a. Named a -> Int)
-> (forall a. Eq a => a -> Named a -> Bool)
-> (forall a. Ord a => Named a -> a)
-> (forall a. Ord a => Named a -> a)
-> (forall a. Num a => Named a -> a)
-> (forall a. Num a => Named a -> a)
-> Foldable Named
forall a. Eq a => a -> Named a -> Bool
forall a. Num a => Named a -> a
forall a. Ord a => Named a -> a
forall m. Monoid m => Named m -> m
forall a. Named a -> Bool
forall a. Named a -> Int
forall a. Named a -> [a]
forall a. (a -> a -> a) -> Named a -> a
forall m a. Monoid m => (a -> m) -> Named a -> m
forall b a. (b -> a -> b) -> b -> Named a -> b
forall a b. (a -> b -> b) -> b -> Named a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => Named m -> m
fold :: forall m. Monoid m => Named m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Named a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Named a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Named a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> Named a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> Named a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Named a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Named a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Named a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Named a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Named a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Named a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> Named a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> Named a -> a
foldr1 :: forall a. (a -> a -> a) -> Named a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Named a -> a
foldl1 :: forall a. (a -> a -> a) -> Named a -> a
$ctoList :: forall a. Named a -> [a]
toList :: forall a. Named a -> [a]
$cnull :: forall a. Named a -> Bool
null :: forall a. Named a -> Bool
$clength :: forall a. Named a -> Int
length :: forall a. Named a -> Int
$celem :: forall a. Eq a => a -> Named a -> Bool
elem :: forall a. Eq a => a -> Named a -> Bool
$cmaximum :: forall a. Ord a => Named a -> a
maximum :: forall a. Ord a => Named a -> a
$cminimum :: forall a. Ord a => Named a -> a
minimum :: forall a. Ord a => Named a -> a
$csum :: forall a. Num a => Named a -> a
sum :: forall a. Num a => Named a -> a
$cproduct :: forall a. Num a => Named a -> a
product :: forall a. Num a => Named a -> a
Foldable, Functor Named
Foldable Named
(Functor Named, Foldable Named) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Named a -> f (Named b))
-> (forall (f :: * -> *) a.
Applicative f =>
Named (f a) -> f (Named a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Named a -> m (Named b))
-> (forall (m :: * -> *) a. Monad m => Named (m a) -> m (Named a))
-> Traversable Named
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Named (m a) -> m (Named a)
forall (f :: * -> *) a. Applicative f => Named (f a) -> f (Named a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Named a -> m (Named b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Named a -> f (Named b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Named a -> f (Named b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Named a -> f (Named b)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Named (f a) -> f (Named a)
sequenceA :: forall (f :: * -> *) a. Applicative f => Named (f a) -> f (Named a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Named a -> m (Named b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Named a -> m (Named b)
$csequence :: forall (m :: * -> *) a. Monad m => Named (m a) -> m (Named a)
sequence :: forall (m :: * -> *) a. Monad m => Named (m a) -> m (Named a)
Traversable, (forall x. Named a -> Rep (Named a) x)
-> (forall x. Rep (Named a) x -> Named a) -> Generic (Named a)
forall x. Rep (Named a) x -> Named a
forall x. Named a -> Rep (Named a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Named a) x -> Named a
forall a x. Named a -> Rep (Named a) x
$cfrom :: forall a x. Named a -> Rep (Named a) x
from :: forall x. Named a -> Rep (Named a) x
$cto :: forall a x. Rep (Named a) x -> Named a
to :: forall x. Rep (Named a) x -> Named a
Generic, Named a -> ()
(Named a -> ()) -> NFData (Named a)
forall a. NFData a => Named a -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall a. NFData a => Named a -> ()
rnf :: Named a -> ()
NFData, (forall a b. (a -> b) -> Named a -> Named b)
-> (forall a b. a -> Named b -> Named a) -> Functor Named
forall a b. a -> Named b -> Named a
forall a b. (a -> b) -> Named a -> Named b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Named a -> Named b
fmap :: forall a b. (a -> b) -> Named a -> Named b
$c<$ :: forall a b. a -> Named b -> Named a
<$ :: forall a b. a -> Named b -> Named a
Functor)
data Schema n = Forall [TParam n] [Prop n] (Type n) (Maybe Range)
deriving (Schema n -> Schema n -> Bool
(Schema n -> Schema n -> Bool)
-> (Schema n -> Schema n -> Bool) -> Eq (Schema n)
forall n. Eq n => Schema n -> Schema n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n. Eq n => Schema n -> Schema n -> Bool
== :: Schema n -> Schema n -> Bool
$c/= :: forall n. Eq n => Schema n -> Schema n -> Bool
/= :: Schema n -> Schema n -> Bool
Eq, Int -> Schema n -> ShowS
[Schema n] -> ShowS
Schema n -> String
(Int -> Schema n -> ShowS)
-> (Schema n -> String) -> ([Schema n] -> ShowS) -> Show (Schema n)
forall n. Show n => Int -> Schema n -> ShowS
forall n. Show n => [Schema n] -> ShowS
forall n. Show n => Schema n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> Schema n -> ShowS
showsPrec :: Int -> Schema n -> ShowS
$cshow :: forall n. Show n => Schema n -> String
show :: Schema n -> String
$cshowList :: forall n. Show n => [Schema n] -> ShowS
showList :: [Schema n] -> ShowS
Show, (forall x. Schema n -> Rep (Schema n) x)
-> (forall x. Rep (Schema n) x -> Schema n) -> Generic (Schema n)
forall x. Rep (Schema n) x -> Schema n
forall x. Schema n -> Rep (Schema n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (Schema n) x -> Schema n
forall n x. Schema n -> Rep (Schema n) x
$cfrom :: forall n x. Schema n -> Rep (Schema n) x
from :: forall x. Schema n -> Rep (Schema n) x
$cto :: forall n x. Rep (Schema n) x -> Schema n
to :: forall x. Rep (Schema n) x -> Schema n
Generic, Schema n -> ()
(Schema n -> ()) -> NFData (Schema n)
forall n. NFData n => Schema n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => Schema n -> ()
rnf :: Schema n -> ()
NFData, (forall a b. (a -> b) -> Schema a -> Schema b)
-> (forall a b. a -> Schema b -> Schema a) -> Functor Schema
forall a b. a -> Schema b -> Schema a
forall a b. (a -> b) -> Schema a -> Schema b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Schema a -> Schema b
fmap :: forall a b. (a -> b) -> Schema a -> Schema b
$c<$ :: forall a b. a -> Schema b -> Schema a
<$ :: forall a b. a -> Schema b -> Schema a
Functor)
data Kind = KProp | KNum | KType | KFun Kind Kind
deriving (Kind -> Kind -> Bool
(Kind -> Kind -> Bool) -> (Kind -> Kind -> Bool) -> Eq Kind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Kind -> Kind -> Bool
== :: Kind -> Kind -> Bool
$c/= :: Kind -> Kind -> Bool
/= :: Kind -> Kind -> Bool
Eq, Int -> Kind -> ShowS
[Kind] -> ShowS
Kind -> String
(Int -> Kind -> ShowS)
-> (Kind -> String) -> ([Kind] -> ShowS) -> Show Kind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Kind -> ShowS
showsPrec :: Int -> Kind -> ShowS
$cshow :: Kind -> String
show :: Kind -> String
$cshowList :: [Kind] -> ShowS
showList :: [Kind] -> ShowS
Show, (forall x. Kind -> Rep Kind x)
-> (forall x. Rep Kind x -> Kind) -> Generic Kind
forall x. Rep Kind x -> Kind
forall x. Kind -> Rep Kind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Kind -> Rep Kind x
from :: forall x. Kind -> Rep Kind x
$cto :: forall x. Rep Kind x -> Kind
to :: forall x. Rep Kind x -> Kind
Generic, Kind -> ()
(Kind -> ()) -> NFData Kind
forall a. (a -> ()) -> NFData a
$crnf :: Kind -> ()
rnf :: Kind -> ()
NFData)
data TParam n = TParam { forall n. TParam n -> n
tpName :: n
, forall n. TParam n -> Maybe Kind
tpKind :: Maybe Kind
, forall n. TParam n -> Maybe Range
tpRange :: Maybe Range
}
deriving (TParam n -> TParam n -> Bool
(TParam n -> TParam n -> Bool)
-> (TParam n -> TParam n -> Bool) -> Eq (TParam n)
forall n. Eq n => TParam n -> TParam n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n. Eq n => TParam n -> TParam n -> Bool
== :: TParam n -> TParam n -> Bool
$c/= :: forall n. Eq n => TParam n -> TParam n -> Bool
/= :: TParam n -> TParam n -> Bool
Eq, Int -> TParam n -> ShowS
[TParam n] -> ShowS
TParam n -> String
(Int -> TParam n -> ShowS)
-> (TParam n -> String) -> ([TParam n] -> ShowS) -> Show (TParam n)
forall n. Show n => Int -> TParam n -> ShowS
forall n. Show n => [TParam n] -> ShowS
forall n. Show n => TParam n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> TParam n -> ShowS
showsPrec :: Int -> TParam n -> ShowS
$cshow :: forall n. Show n => TParam n -> String
show :: TParam n -> String
$cshowList :: forall n. Show n => [TParam n] -> ShowS
showList :: [TParam n] -> ShowS
Show, (forall x. TParam n -> Rep (TParam n) x)
-> (forall x. Rep (TParam n) x -> TParam n) -> Generic (TParam n)
forall x. Rep (TParam n) x -> TParam n
forall x. TParam n -> Rep (TParam n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (TParam n) x -> TParam n
forall n x. TParam n -> Rep (TParam n) x
$cfrom :: forall n x. TParam n -> Rep (TParam n) x
from :: forall x. TParam n -> Rep (TParam n) x
$cto :: forall n x. Rep (TParam n) x -> TParam n
to :: forall x. Rep (TParam n) x -> TParam n
Generic, TParam n -> ()
(TParam n -> ()) -> NFData (TParam n)
forall n. NFData n => TParam n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => TParam n -> ()
rnf :: TParam n -> ()
NFData, (forall a b. (a -> b) -> TParam a -> TParam b)
-> (forall a b. a -> TParam b -> TParam a) -> Functor TParam
forall a b. a -> TParam b -> TParam a
forall a b. (a -> b) -> TParam a -> TParam b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> TParam a -> TParam b
fmap :: forall a b. (a -> b) -> TParam a -> TParam b
$c<$ :: forall a b. a -> TParam b -> TParam a
<$ :: forall a b. a -> TParam b -> TParam a
Functor)
data Type n = TFun (Type n) (Type n)
| TSeq (Type n) (Type n)
| TBit
| TNum Integer
| TChar Char
| TUser n [Type n]
| TTyApp [Named (Type n)]
| TRecord (Rec (Type n))
| TTuple [Type n]
| TWild
| TLocated (Type n) Range
| TParens (Type n) (Maybe Kind)
| TInfix (Type n) (Located n) Fixity (Type n)
deriving (Type n -> Type n -> Bool
(Type n -> Type n -> Bool)
-> (Type n -> Type n -> Bool) -> Eq (Type n)
forall n. Eq n => Type n -> Type n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n. Eq n => Type n -> Type n -> Bool
== :: Type n -> Type n -> Bool
$c/= :: forall n. Eq n => Type n -> Type n -> Bool
/= :: Type n -> Type n -> Bool
Eq, Int -> Type n -> ShowS
[Type n] -> ShowS
Type n -> String
(Int -> Type n -> ShowS)
-> (Type n -> String) -> ([Type n] -> ShowS) -> Show (Type n)
forall n. Show n => Int -> Type n -> ShowS
forall n. Show n => [Type n] -> ShowS
forall n. Show n => Type n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> Type n -> ShowS
showsPrec :: Int -> Type n -> ShowS
$cshow :: forall n. Show n => Type n -> String
show :: Type n -> String
$cshowList :: forall n. Show n => [Type n] -> ShowS
showList :: [Type n] -> ShowS
Show, (forall x. Type n -> Rep (Type n) x)
-> (forall x. Rep (Type n) x -> Type n) -> Generic (Type n)
forall x. Rep (Type n) x -> Type n
forall x. Type n -> Rep (Type n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (Type n) x -> Type n
forall n x. Type n -> Rep (Type n) x
$cfrom :: forall n x. Type n -> Rep (Type n) x
from :: forall x. Type n -> Rep (Type n) x
$cto :: forall n x. Rep (Type n) x -> Type n
to :: forall x. Rep (Type n) x -> Type n
Generic, Type n -> ()
(Type n -> ()) -> NFData (Type n)
forall n. NFData n => Type n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => Type n -> ()
rnf :: Type n -> ()
NFData, (forall a b. (a -> b) -> Type a -> Type b)
-> (forall a b. a -> Type b -> Type a) -> Functor Type
forall a b. a -> Type b -> Type a
forall a b. (a -> b) -> Type a -> Type b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Type a -> Type b
fmap :: forall a b. (a -> b) -> Type a -> Type b
$c<$ :: forall a b. a -> Type b -> Type a
<$ :: forall a b. a -> Type b -> Type a
Functor)
newtype Prop n = CType (Type n)
deriving (Prop n -> Prop n -> Bool
(Prop n -> Prop n -> Bool)
-> (Prop n -> Prop n -> Bool) -> Eq (Prop n)
forall n. Eq n => Prop n -> Prop n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n. Eq n => Prop n -> Prop n -> Bool
== :: Prop n -> Prop n -> Bool
$c/= :: forall n. Eq n => Prop n -> Prop n -> Bool
/= :: Prop n -> Prop n -> Bool
Eq, Int -> Prop n -> ShowS
[Prop n] -> ShowS
Prop n -> String
(Int -> Prop n -> ShowS)
-> (Prop n -> String) -> ([Prop n] -> ShowS) -> Show (Prop n)
forall n. Show n => Int -> Prop n -> ShowS
forall n. Show n => [Prop n] -> ShowS
forall n. Show n => Prop n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> Prop n -> ShowS
showsPrec :: Int -> Prop n -> ShowS
$cshow :: forall n. Show n => Prop n -> String
show :: Prop n -> String
$cshowList :: forall n. Show n => [Prop n] -> ShowS
showList :: [Prop n] -> ShowS
Show, (forall x. Prop n -> Rep (Prop n) x)
-> (forall x. Rep (Prop n) x -> Prop n) -> Generic (Prop n)
forall x. Rep (Prop n) x -> Prop n
forall x. Prop n -> Rep (Prop n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (Prop n) x -> Prop n
forall n x. Prop n -> Rep (Prop n) x
$cfrom :: forall n x. Prop n -> Rep (Prop n) x
from :: forall x. Prop n -> Rep (Prop n) x
$cto :: forall n x. Rep (Prop n) x -> Prop n
to :: forall x. Rep (Prop n) x -> Prop n
Generic, Prop n -> ()
(Prop n -> ()) -> NFData (Prop n)
forall n. NFData n => Prop n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => Prop n -> ()
rnf :: Prop n -> ()
NFData, (forall a b. (a -> b) -> Prop a -> Prop b)
-> (forall a b. a -> Prop b -> Prop a) -> Functor Prop
forall a b. a -> Prop b -> Prop a
forall a b. (a -> b) -> Prop a -> Prop b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Prop a -> Prop b
fmap :: forall a b. (a -> b) -> Prop a -> Prop b
$c<$ :: forall a b. a -> Prop b -> Prop a
<$ :: forall a b. a -> Prop b -> Prop a
Functor)
instance AddLoc (Expr n) where
addLoc :: Expr n -> Range -> Expr n
addLoc x :: Expr n
x@ELocated{} Range
_ = Expr n
x
addLoc Expr n
x Range
r = Expr n -> Range -> Expr n
forall n. Expr n -> Range -> Expr n
ELocated Expr n
x Range
r
dropLoc :: Expr n -> Expr n
dropLoc (ELocated Expr n
e Range
_) = Expr n -> Expr n
forall t. AddLoc t => t -> t
dropLoc Expr n
e
dropLoc Expr n
e = Expr n
e
instance HasLoc (Expr name) where
getLoc :: Expr name -> Maybe Range
getLoc (ELocated Expr name
_ Range
r) = Range -> Maybe Range
forall a. a -> Maybe a
Just Range
r
getLoc Expr name
_ = Maybe Range
forall a. Maybe a
Nothing
instance HasLoc (TParam name) where
getLoc :: TParam name -> Maybe Range
getLoc (TParam name
_ Maybe Kind
_ Maybe Range
r) = Maybe Range
r
instance AddLoc (TParam name) where
addLoc :: TParam name -> Range -> TParam name
addLoc (TParam name
a Maybe Kind
b Maybe Range
_) Range
l = name -> Maybe Kind -> Maybe Range -> TParam name
forall n. n -> Maybe Kind -> Maybe Range -> TParam n
TParam name
a Maybe Kind
b (Range -> Maybe Range
forall a. a -> Maybe a
Just Range
l)
dropLoc :: TParam name -> TParam name
dropLoc (TParam name
a Maybe Kind
b Maybe Range
_) = name -> Maybe Kind -> Maybe Range -> TParam name
forall n. n -> Maybe Kind -> Maybe Range -> TParam n
TParam name
a Maybe Kind
b Maybe Range
forall a. Maybe a
Nothing
instance HasLoc (Type name) where
getLoc :: Type name -> Maybe Range
getLoc (TLocated Type name
_ Range
r) = Range -> Maybe Range
forall a. a -> Maybe a
Just Range
r
getLoc Type name
_ = Maybe Range
forall a. Maybe a
Nothing
instance AddLoc (Type name) where
addLoc :: Type name -> Range -> Type name
addLoc = Type name -> Range -> Type name
forall name. Type name -> Range -> Type name
TLocated
dropLoc :: Type name -> Type name
dropLoc (TLocated Type name
e Range
_) = Type name -> Type name
forall t. AddLoc t => t -> t
dropLoc Type name
e
dropLoc Type name
e = Type name
e
instance AddLoc (Pattern name) where
addLoc :: Pattern name -> Range -> Pattern name
addLoc = Pattern name -> Range -> Pattern name
forall name. Pattern name -> Range -> Pattern name
PLocated
dropLoc :: Pattern name -> Pattern name
dropLoc (PLocated Pattern name
e Range
_) = Pattern name -> Pattern name
forall t. AddLoc t => t -> t
dropLoc Pattern name
e
dropLoc Pattern name
e = Pattern name
e
instance HasLoc (Pattern name) where
getLoc :: Pattern name -> Maybe Range
getLoc (PLocated Pattern name
_ Range
r) = Range -> Maybe Range
forall a. a -> Maybe a
Just Range
r
getLoc (PTyped Pattern name
r Type name
_) = Pattern name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc Pattern name
r
getLoc (PVar Located name
x) = Located name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc Located name
x
getLoc Pattern name
_ = Maybe Range
forall a. Maybe a
Nothing
instance HasLoc (Bind name) where
getLoc :: Bind name -> Maybe Range
getLoc Bind name
b = (Located name, Located (BindDef name)) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (Bind name -> Located name
forall name. Bind name -> Located name
bName Bind name
b, Bind name -> Located (BindDef name)
forall name. Bind name -> Located (BindDef name)
bDef Bind name
b)
instance HasLoc (Match name) where
getLoc :: Match name -> Maybe Range
getLoc (Match Pattern name
p Expr name
e) = (Pattern name, Expr name) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (Pattern name
p,Expr name
e)
getLoc (MatchLet Bind name
b) = Bind name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc Bind name
b
instance HasLoc a => HasLoc (Named a) where
getLoc :: Named a -> Maybe Range
getLoc Named a
l = (Located Ident, a) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (Named a -> Located Ident
forall a. Named a -> Located Ident
name Named a
l, Named a -> a
forall a. Named a -> a
value Named a
l)
instance HasLoc (Schema name) where
getLoc :: Schema name -> Maybe Range
getLoc (Forall [TParam name]
_ [Prop name]
_ Type name
_ Maybe Range
r) = Maybe Range
r
instance AddLoc (Schema name) where
addLoc :: Schema name -> Range -> Schema name
addLoc (Forall [TParam name]
xs [Prop name]
ps Type name
t Maybe Range
_) Range
r = [TParam name]
-> [Prop name] -> Type name -> Maybe Range -> Schema name
forall n.
[TParam n] -> [Prop n] -> Type n -> Maybe Range -> Schema n
Forall [TParam name]
xs [Prop name]
ps Type name
t (Range -> Maybe Range
forall a. a -> Maybe a
Just Range
r)
dropLoc :: Schema name -> Schema name
dropLoc (Forall [TParam name]
xs [Prop name]
ps Type name
t Maybe Range
_) = [TParam name]
-> [Prop name] -> Type name -> Maybe Range -> Schema name
forall n.
[TParam n] -> [Prop n] -> Type n -> Maybe Range -> Schema n
Forall [TParam name]
xs [Prop name]
ps Type name
t Maybe Range
forall a. Maybe a
Nothing
instance HasLoc (Decl name) where
getLoc :: Decl name -> Maybe Range
getLoc (DLocated Decl name
_ Range
r) = Range -> Maybe Range
forall a. a -> Maybe a
Just Range
r
getLoc Decl name
_ = Maybe Range
forall a. Maybe a
Nothing
instance AddLoc (Decl name) where
addLoc :: Decl name -> Range -> Decl name
addLoc Decl name
d Range
r = Decl name -> Range -> Decl name
forall name. Decl name -> Range -> Decl name
DLocated Decl name
d Range
r
dropLoc :: Decl name -> Decl name
dropLoc (DLocated Decl name
d Range
_) = Decl name -> Decl name
forall t. AddLoc t => t -> t
dropLoc Decl name
d
dropLoc Decl name
d = Decl name
d
instance HasLoc a => HasLoc (TopLevel a) where
getLoc :: TopLevel a -> Maybe Range
getLoc = a -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (a -> Maybe Range)
-> (TopLevel a -> a) -> TopLevel a -> Maybe Range
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TopLevel a -> a
forall a. TopLevel a -> a
tlValue
instance HasLoc (TopDecl name) where
getLoc :: TopDecl name -> Maybe Range
getLoc TopDecl name
td =
case TopDecl name
td of
Decl TopLevel (Decl name)
tld -> TopLevel (Decl name) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc TopLevel (Decl name)
tld
DPrimType TopLevel (PrimType name)
pt -> TopLevel (PrimType name) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc TopLevel (PrimType name)
pt
TDNewtype TopLevel (Newtype name)
n -> TopLevel (Newtype name) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc TopLevel (Newtype name)
n
TDEnum TopLevel (EnumDecl name)
n -> TopLevel (EnumDecl name) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc TopLevel (EnumDecl name)
n
Include Located String
lfp -> Located String -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc Located String
lfp
DModule TopLevel (NestedModule name)
d -> TopLevel (NestedModule name) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc TopLevel (NestedModule name)
d
DImport Located (ImportG (ImpName name))
d -> Located (ImportG (ImpName name)) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc Located (ImportG (ImpName name))
d
DModParam ModParam name
d -> ModParam name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc ModParam name
d
DParamDecl Range
r Signature name
_ -> Range -> Maybe Range
forall a. a -> Maybe a
Just Range
r
DInterfaceConstraint Maybe (Located Text)
_ Located [Prop name]
ds -> Located [Prop name] -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc Located [Prop name]
ds
instance HasLoc (ParamDecl name) where
getLoc :: ParamDecl name -> Maybe Range
getLoc ParamDecl name
pd =
case ParamDecl name
pd of
DParameterType ParameterType name
d -> ParameterType name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc ParameterType name
d
DParameterFun ParameterFun name
d -> ParameterFun name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc ParameterFun name
d
DParameterDecl SigDecl name
d -> SigDecl name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc SigDecl name
d
DParameterConstraint ParameterConstraint name
d -> ParameterConstraint name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc ParameterConstraint name
d
instance HasLoc (SigDecl name) where
getLoc :: SigDecl name -> Maybe Range
getLoc SigDecl name
decl =
case SigDecl name
decl of
SigTySyn TySyn name
ts Maybe Text
_ -> TySyn name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc TySyn name
ts
SigPropSyn PropSyn name
ps Maybe Text
_ -> PropSyn name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc PropSyn name
ps
instance HasLoc (ModParam name) where
getLoc :: ModParam name -> Maybe Range
getLoc ModParam name
mp = Located (ImpName name) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (ModParam name -> Located (ImpName name)
forall name. ModParam name -> Located (ImpName name)
mpSignature ModParam name
mp)
instance HasLoc (PrimType name) where
getLoc :: PrimType name -> Maybe Range
getLoc PrimType name
pt = Range -> Maybe Range
forall a. a -> Maybe a
Just (Range -> Range -> Range
rComb (Located name -> Range
forall a. Located a -> Range
srcRange (PrimType name -> Located name
forall name. PrimType name -> Located name
primTName PrimType name
pt)) (Located Kind -> Range
forall a. Located a -> Range
srcRange (PrimType name -> Located Kind
forall name. PrimType name -> Located Kind
primTKind PrimType name
pt)))
instance HasLoc (ParameterType name) where
getLoc :: ParameterType name -> Maybe Range
getLoc ParameterType name
a = Located name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (ParameterType name -> Located name
forall name. ParameterType name -> Located name
ptName ParameterType name
a)
instance HasLoc (ParameterFun name) where
getLoc :: ParameterFun name -> Maybe Range
getLoc ParameterFun name
a = Located name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (ParameterFun name -> Located name
forall name. ParameterFun name -> Located name
pfName ParameterFun name
a)
instance HasLoc (ParameterConstraint name) where
getLoc :: ParameterConstraint name -> Maybe Range
getLoc ParameterConstraint name
a = [Located (Prop name)] -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (ParameterConstraint name -> [Located (Prop name)]
forall name. ParameterConstraint name -> [Located (Prop name)]
pcProps ParameterConstraint name
a)
instance HasLoc (ModuleG mname name) where
getLoc :: ModuleG mname name -> Maybe Range
getLoc ModuleG mname name
m
| [Range] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Range]
locs = Maybe Range
forall a. Maybe a
Nothing
| Bool
otherwise = Range -> Maybe Range
forall a. a -> Maybe a
Just ([Range] -> Range
rCombs [Range]
locs)
where
locs :: [Range]
locs = [Maybe Range] -> [Range]
forall a. [Maybe a] -> [a]
catMaybes [ Located mname -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (ModuleG mname name -> Located mname
forall mname name. ModuleG mname name -> Located mname
mName ModuleG mname name
m)
, [Located Import] -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (ModuleG mname name -> [Located Import]
forall mname name. ModuleG mname name -> [Located Import]
mImports ModuleG mname name
m)
, [TopDecl name] -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (ModuleG mname name -> [TopDecl name]
forall mname name. ModuleG mname name -> [TopDecl name]
mDecls ModuleG mname name
m)
]
instance HasLoc (NestedModule name) where
getLoc :: NestedModule name -> Maybe Range
getLoc (NestedModule ModuleG name name
m) = ModuleG name name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc ModuleG name name
m
instance HasLoc (Newtype name) where
getLoc :: Newtype name -> Maybe Range
getLoc Newtype name
n
| [Range] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Range]
locs = Maybe Range
forall a. Maybe a
Nothing
| Bool
otherwise = Range -> Maybe Range
forall a. a -> Maybe a
Just ([Range] -> Range
rCombs [Range]
locs)
where
locs :: [Range]
locs = [Maybe Range] -> [Range]
forall a. [Maybe a] -> [a]
catMaybes ([ Located name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (Newtype name -> Located name
forall name. Newtype name -> Located name
nName Newtype name
n)] [Maybe Range] -> [Maybe Range] -> [Maybe Range]
forall a. [a] -> [a] -> [a]
++ ((Ident, (Range, Type name)) -> Maybe Range)
-> [(Ident, (Range, Type name))] -> [Maybe Range]
forall a b. (a -> b) -> [a] -> [b]
map (Range -> Maybe Range
forall a. a -> Maybe a
Just (Range -> Maybe Range)
-> ((Ident, (Range, Type name)) -> Range)
-> (Ident, (Range, Type name))
-> Maybe Range
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Range, Type name) -> Range
forall a b. (a, b) -> a
fst ((Range, Type name) -> Range)
-> ((Ident, (Range, Type name)) -> (Range, Type name))
-> (Ident, (Range, Type name))
-> Range
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ident, (Range, Type name)) -> (Range, Type name)
forall a b. (a, b) -> b
snd) (RecordMap Ident (Range, Type name) -> [(Ident, (Range, Type name))]
forall a b. (Show a, Ord a) => RecordMap a b -> [(a, b)]
displayFields (Newtype name -> RecordMap Ident (Range, Type name)
forall name. Newtype name -> Rec (Type name)
nBody Newtype name
n)))
instance HasLoc (EnumDecl name) where
getLoc :: EnumDecl name -> Maybe Range
getLoc EnumDecl name
n
| [Range] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Range]
locs = Maybe Range
forall a. Maybe a
Nothing
| Bool
otherwise = Range -> Maybe Range
forall a. a -> Maybe a
Just ([Range] -> Range
rCombs [Range]
locs)
where
locs :: [Range]
locs = [Maybe Range] -> [Range]
forall a. [Maybe a] -> [a]
catMaybes (Located name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (EnumDecl name -> Located name
forall name. EnumDecl name -> Located name
eName EnumDecl name
n) Maybe Range -> [Maybe Range] -> [Maybe Range]
forall a. a -> [a] -> [a]
: (TopLevel (EnumCon name) -> Maybe Range)
-> [TopLevel (EnumCon name)] -> [Maybe Range]
forall a b. (a -> b) -> [a] -> [b]
map TopLevel (EnumCon name) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (EnumDecl name -> [TopLevel (EnumCon name)]
forall name. EnumDecl name -> [TopLevel (EnumCon name)]
eCons EnumDecl name
n))
instance HasLoc (EnumCon name) where
getLoc :: EnumCon name -> Maybe Range
getLoc EnumCon name
c
| [Range] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Range]
locs = Maybe Range
forall a. Maybe a
Nothing
| Bool
otherwise = Range -> Maybe Range
forall a. a -> Maybe a
Just ([Range] -> Range
rCombs [Range]
locs)
where
locs :: [Range]
locs = [Maybe Range] -> [Range]
forall a. [Maybe a] -> [a]
catMaybes (Located name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (EnumCon name -> Located name
forall name. EnumCon name -> Located name
ecName EnumCon name
c) Maybe Range -> [Maybe Range] -> [Maybe Range]
forall a. a -> [a] -> [a]
: (Type name -> Maybe Range) -> [Type name] -> [Maybe Range]
forall a b. (a -> b) -> [a] -> [b]
map Type name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (EnumCon name -> [Type name]
forall name. EnumCon name -> [Type name]
ecFields EnumCon name
c))
instance HasLoc (TySyn name) where
getLoc :: TySyn name -> Maybe Range
getLoc (TySyn Located name
x Maybe Fixity
_ [TParam name]
_ Type name
_) = Located name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc Located name
x
instance HasLoc (PropSyn name) where
getLoc :: PropSyn name -> Maybe Range
getLoc (PropSyn Located name
x Maybe Fixity
_ [TParam name]
_ [Prop name]
_) = Located name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc Located name
x
instance HasLoc (PropGuardCase name) where
getLoc :: PropGuardCase name -> Maybe Range
getLoc PropGuardCase name
n
| [Range] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Range]
locs = Maybe Range
forall a. Maybe a
Nothing
| Bool
otherwise = Range -> Maybe Range
forall a. a -> Maybe a
Just ([Range] -> Range
rCombs [Range]
locs)
where
locs :: [Range]
locs = [Maybe Range] -> [Range]
forall a. [Maybe a] -> [a]
catMaybes (Expr name -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (PropGuardCase name -> Expr name
forall name. PropGuardCase name -> Expr name
pgcExpr PropGuardCase name
n) Maybe Range -> [Maybe Range] -> [Maybe Range]
forall a. a -> [a] -> [a]
: (Located (Prop name) -> Maybe Range)
-> [Located (Prop name)] -> [Maybe Range]
forall a b. (a -> b) -> [a] -> [b]
map Located (Prop name) -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc (PropGuardCase name -> [Located (Prop name)]
forall name. PropGuardCase name -> [Located (Prop name)]
pgcProps PropGuardCase name
n))
instance HasLoc (BindParams name) where
getLoc :: BindParams name -> Maybe Range
getLoc BindParams name
bps = case BindParams name
bps of
PatternParams [Pattern name]
ps -> [Pattern name] -> Maybe Range
forall t. HasLoc t => t -> Maybe Range
getLoc [Pattern name]
ps
DroppedParams Maybe Range
rng Int
_ -> Maybe Range
rng
ppL :: PP a => Located a -> Doc
ppL :: forall a. PP a => Located a -> Doc
ppL = a -> Doc
forall a. PP a => a -> Doc
pp (a -> Doc) -> (Located a -> a) -> Located a -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located a -> a
forall a. Located a -> a
thing
ppNamed :: PP a => String -> Named a -> Doc
ppNamed :: forall a. PP a => String -> Named a -> Doc
ppNamed String
s Named a
x = Located Ident -> Doc
forall a. PP a => Located a -> Doc
ppL (Named a -> Located Ident
forall a. Named a -> Located Ident
name Named a
x) Doc -> Doc -> Doc
<+> String -> Doc
text String
s Doc -> Doc -> Doc
<+> a -> Doc
forall a. PP a => a -> Doc
pp (Named a -> a
forall a. Named a -> a
value Named a
x)
ppNamed' :: PP a => String -> (Ident, (Range, a)) -> Doc
ppNamed' :: forall a. PP a => String -> (Ident, (Range, a)) -> Doc
ppNamed' String
s (Ident
i,(Range
_,a
v)) = Ident -> Doc
forall a. PP a => a -> Doc
pp Ident
i Doc -> Doc -> Doc
<+> String -> Doc
text String
s Doc -> Doc -> Doc
<+> a -> Doc
forall a. PP a => a -> Doc
pp a
v
instance (Show name, PPName mname, PPName name) => PP (ModuleG mname name) where
ppPrec :: Int -> ModuleG mname name -> Doc
ppPrec Int
_ = Doc -> ModuleG mname name -> Doc
forall name mname.
(Show name, PPName mname, PPName name) =>
Doc -> ModuleG mname name -> Doc
ppModule Doc
"module"
instance (Show name, PPName name) => PP (NestedModule name) where
ppPrec :: Int -> NestedModule name -> Doc
ppPrec Int
_ (NestedModule ModuleG name name
m) = Doc -> ModuleG name name -> Doc
forall name mname.
(Show name, PPName mname, PPName name) =>
Doc -> ModuleG mname name -> Doc
ppModule Doc
"submodule" ModuleG name name
m
ppModule :: (Show name, PPName mname, PPName name) =>
Doc -> ModuleG mname name -> Doc
ppModule :: forall name mname.
(Show name, PPName mname, PPName name) =>
Doc -> ModuleG mname name -> Doc
ppModule Doc
kw ModuleG mname name
m = Doc
kw' Doc -> Doc -> Doc
<+> Located mname -> Doc
forall a. PP a => Located a -> Doc
ppL (ModuleG mname name -> Located mname
forall mname name. ModuleG mname name -> Located mname
mName ModuleG mname name
m) Doc -> Doc -> Doc
<+> ModuleDefinition name -> Doc
forall a. PP a => a -> Doc
pp (ModuleG mname name -> ModuleDefinition name
forall mname name. ModuleG mname name -> ModuleDefinition name
mDef ModuleG mname name
m)
Doc -> Doc -> Doc
$$ Int -> Doc -> Doc
indent Int
2 ([Doc] -> Doc
vcat [Doc
"/* In scope:", Int -> Doc -> Doc
indent Int
2 (NamingEnv -> Doc
forall a. PP a => a -> Doc
pp (ModuleG mname name -> NamingEnv
forall mname name. ModuleG mname name -> NamingEnv
mInScope ModuleG mname name
m)), Doc
" */"])
where
kw' :: Doc
kw' = case ModuleG mname name -> ModuleDefinition name
forall mname name. ModuleG mname name -> ModuleDefinition name
mDef ModuleG mname name
m of
InterfaceModule {} -> Doc
"interface" Doc -> Doc -> Doc
<+> Doc
kw
ModuleDefinition name
_ -> Doc
kw
instance (Show name, PPName name) => PP (ModuleDefinition name) where
ppPrec :: Int -> ModuleDefinition name -> Doc
ppPrec Int
_ ModuleDefinition name
def =
case ModuleDefinition name
def of
NormalModule [TopDecl name]
ds -> Doc
"where" Doc -> Doc -> Doc
$$ Int -> Doc -> Doc
indent Int
2 ([Doc] -> Doc
vcat ((TopDecl name -> Doc) -> [TopDecl name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map TopDecl name -> Doc
forall a. PP a => a -> Doc
pp [TopDecl name]
ds))
FunctorInstance Located (ImpName name)
f ModuleInstanceArgs name
as ModuleInstance name
inst -> [Doc] -> Doc
vcat ( (Doc
"=" Doc -> Doc -> Doc
<+> ImpName name -> Doc
forall a. PP a => a -> Doc
pp (Located (ImpName name) -> ImpName name
forall a. Located a -> a
thing Located (ImpName name)
f) Doc -> Doc -> Doc
<+> ModuleInstanceArgs name -> Doc
forall a. PP a => a -> Doc
pp ModuleInstanceArgs name
as)
Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: [Doc]
ppInst
)
where
ppInst :: [Doc]
ppInst = if ModuleInstance name -> Bool
forall a. Map name a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ModuleInstance name
inst then [] else [ Int -> Doc -> Doc
indent Int
2
([Doc] -> Doc
vcat (Doc
"/* Instance:" Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
:
[Doc]
instLines [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc
" */"]))
]
instLines :: [Doc]
instLines = [ Doc
" *" Doc -> Doc -> Doc
<+> name -> Doc
forall a. PP a => a -> Doc
pp name
k Doc -> Doc -> Doc
<+> Doc
"->" Doc -> Doc -> Doc
<+> name -> Doc
forall a. PP a => a -> Doc
pp name
v
| (name
k,name
v) <- ModuleInstance name -> [(name, name)]
forall k a. Map k a -> [(k, a)]
Map.toList ModuleInstance name
inst ]
InterfaceModule Signature name
s -> Doc -> Signature name -> Doc
forall name.
(Show name, PPName name) =>
Doc -> Signature name -> Doc
ppInterface Doc
"where" Signature name
s
instance (Show name, PPName name) => PP (ModuleInstanceArgs name) where
ppPrec :: Int -> ModuleInstanceArgs name -> Doc
ppPrec Int
_ ModuleInstanceArgs name
arg =
case ModuleInstanceArgs name
arg of
DefaultInstArg Located (ModuleInstanceArg name)
x -> Doc -> Doc
braces (ModuleInstanceArg name -> Doc
forall a. PP a => a -> Doc
pp (Located (ModuleInstanceArg name) -> ModuleInstanceArg name
forall a. Located a -> a
thing Located (ModuleInstanceArg name)
x))
DefaultInstAnonArg [TopDecl name]
ds -> Doc
"where" Doc -> Doc -> Doc
$$ Int -> Doc -> Doc
indent Int
2 ([Doc] -> Doc
vcat ((TopDecl name -> Doc) -> [TopDecl name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map TopDecl name -> Doc
forall a. PP a => a -> Doc
pp [TopDecl name]
ds))
NamedInstArgs [ModuleInstanceNamedArg name]
xs -> Doc -> Doc
braces ([Doc] -> Doc
commaSep ((ModuleInstanceNamedArg name -> Doc)
-> [ModuleInstanceNamedArg name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ModuleInstanceNamedArg name -> Doc
forall a. PP a => a -> Doc
pp [ModuleInstanceNamedArg name]
xs))
instance (Show name, PPName name) => PP (ModuleInstanceNamedArg name) where
ppPrec :: Int -> ModuleInstanceNamedArg name -> Doc
ppPrec Int
_ (ModuleInstanceNamedArg Located Ident
x Located (ModuleInstanceArg name)
y) = Ident -> Doc
forall a. PP a => a -> Doc
pp (Located Ident -> Ident
forall a. Located a -> a
thing Located Ident
x) Doc -> Doc -> Doc
<+> Doc
"=" Doc -> Doc -> Doc
<+> ModuleInstanceArg name -> Doc
forall a. PP a => a -> Doc
pp (Located (ModuleInstanceArg name) -> ModuleInstanceArg name
forall a. Located a -> a
thing Located (ModuleInstanceArg name)
y)
instance (Show name, PPName name) => PP (ModuleInstanceArg name) where
ppPrec :: Int -> ModuleInstanceArg name -> Doc
ppPrec Int
_ ModuleInstanceArg name
arg =
case ModuleInstanceArg name
arg of
ModuleArg ImpName name
x -> ImpName name -> Doc
forall a. PP a => a -> Doc
pp ImpName name
x
ParameterArg Ident
i -> Doc
"parameter" Doc -> Doc -> Doc
<+> Ident -> Doc
forall a. PP a => a -> Doc
pp Ident
i
ModuleInstanceArg name
AddParams -> Doc
"{}"
instance (Show name, PPName name) => PP (Program name) where
ppPrec :: Int -> Program name -> Doc
ppPrec Int
_ (Program [TopDecl name]
ds) = [Doc] -> Doc
vcat ((TopDecl name -> Doc) -> [TopDecl name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map TopDecl name -> Doc
forall a. PP a => a -> Doc
pp [TopDecl name]
ds)
instance (Show name, PPName name) => PP (TopDecl name) where
ppPrec :: Int -> TopDecl name -> Doc
ppPrec Int
_ TopDecl name
top_decl =
case TopDecl name
top_decl of
Decl TopLevel (Decl name)
d -> TopLevel (Decl name) -> Doc
forall a. PP a => a -> Doc
pp TopLevel (Decl name)
d
DPrimType TopLevel (PrimType name)
p -> TopLevel (PrimType name) -> Doc
forall a. PP a => a -> Doc
pp TopLevel (PrimType name)
p
TDNewtype TopLevel (Newtype name)
n -> TopLevel (Newtype name) -> Doc
forall a. PP a => a -> Doc
pp TopLevel (Newtype name)
n
TDEnum TopLevel (EnumDecl name)
n -> TopLevel (EnumDecl name) -> Doc
forall a. PP a => a -> Doc
pp TopLevel (EnumDecl name)
n
Include Located String
l -> String -> Doc
text String
"include" Doc -> Doc -> Doc
<+> String -> Doc
text (ShowS
forall a. Show a => a -> String
show (Located String -> String
forall a. Located a -> a
thing Located String
l))
DModule TopLevel (NestedModule name)
d -> TopLevel (NestedModule name) -> Doc
forall a. PP a => a -> Doc
pp TopLevel (NestedModule name)
d
DImport Located (ImportG (ImpName name))
i -> ImportG (ImpName name) -> Doc
forall a. PP a => a -> Doc
pp (Located (ImportG (ImpName name)) -> ImportG (ImpName name)
forall a. Located a -> a
thing Located (ImportG (ImpName name))
i)
DModParam ModParam name
s -> ModParam name -> Doc
forall a. PP a => a -> Doc
pp ModParam name
s
DParamDecl Range
_ Signature name
ds -> Doc -> Signature name -> Doc
forall name.
(Show name, PPName name) =>
Doc -> Signature name -> Doc
ppInterface Doc
"parameter" Signature name
ds
DInterfaceConstraint Maybe (Located Text)
_ Located [Prop name]
ds ->
Doc
"interface constraint" Doc -> Doc -> Doc
<+>
case (Prop name -> Doc) -> [Prop name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Prop name -> Doc
forall a. PP a => a -> Doc
pp (Located [Prop name] -> [Prop name]
forall a. Located a -> a
thing Located [Prop name]
ds) of
[Doc
x] -> Doc
x
[] -> Doc
"()"
[Doc]
xs -> Int -> Doc -> Doc
nest Int
1 (Doc -> Doc
parens ([Doc] -> Doc
commaSepFill [Doc]
xs))
instance (Show name, PPName name) => PP (ParamDecl name) where
ppPrec :: Int -> ParamDecl name -> Doc
ppPrec Int
_ ParamDecl name
pd =
case ParamDecl name
pd of
DParameterFun ParameterFun name
d -> ParameterFun name -> Doc
forall a. PP a => a -> Doc
pp ParameterFun name
d
DParameterType ParameterType name
d -> ParameterType name -> Doc
forall a. PP a => a -> Doc
pp ParameterType name
d
DParameterDecl SigDecl name
d -> SigDecl name -> Doc
forall a. PP a => a -> Doc
pp SigDecl name
d
DParameterConstraint ParameterConstraint name
d -> ParameterConstraint name -> Doc
forall a. PP a => a -> Doc
pp ParameterConstraint name
d
ppInterface :: (Show name, PPName name) => Doc -> Signature name -> Doc
ppInterface :: forall name.
(Show name, PPName name) =>
Doc -> Signature name -> Doc
ppInterface Doc
kw Signature name
sig = Doc
kw Doc -> Doc -> Doc
$$ Int -> Doc -> Doc
indent Int
2 ([Doc] -> Doc
vcat ([Doc]
is [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc]
ds))
where
is :: [Doc]
is = (Located (ImportG (ImpName name)) -> Doc)
-> [Located (ImportG (ImpName name))] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Located (ImportG (ImpName name)) -> Doc
forall a. PP a => a -> Doc
pp (Signature name -> [Located (ImportG (ImpName name))]
forall name. Signature name -> [Located (ImportG (ImpName name))]
sigImports Signature name
sig)
cs :: [Doc]
cs = case Signature name -> [Located (Prop name)]
forall name. Signature name -> [Located (Prop name)]
sigConstraints Signature name
sig of
[] -> []
[Located (Prop name)]
cs' -> [Doc
"type constraint" Doc -> Doc -> Doc
<+>
Doc -> Doc
parens ([Doc] -> Doc
commaSep ((Located (Prop name) -> Doc) -> [Located (Prop name)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Prop name -> Doc
forall a. PP a => a -> Doc
pp (Prop name -> Doc)
-> (Located (Prop name) -> Prop name) -> Located (Prop name) -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located (Prop name) -> Prop name
forall a. Located a -> a
thing) [Located (Prop name)]
cs'))]
ds :: [Doc]
ds = (ParameterType name -> Doc) -> [ParameterType name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ParameterType name -> Doc
forall a. PP a => a -> Doc
pp (Signature name -> [ParameterType name]
forall name. Signature name -> [ParameterType name]
sigTypeParams Signature name
sig)
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ (SigDecl name -> Doc) -> [SigDecl name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map SigDecl name -> Doc
forall a. PP a => a -> Doc
pp (Signature name -> [SigDecl name]
forall name. Signature name -> [SigDecl name]
sigDecls Signature name
sig)
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc]
cs
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ (ParameterFun name -> Doc) -> [ParameterFun name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ParameterFun name -> Doc
forall a. PP a => a -> Doc
pp (Signature name -> [ParameterFun name]
forall name. Signature name -> [ParameterFun name]
sigFunParams Signature name
sig)
instance (Show name, PPName name) => PP (SigDecl name) where
ppPrec :: Int -> SigDecl name -> Doc
ppPrec Int
p SigDecl name
decl =
case SigDecl name
decl of
SigTySyn TySyn name
ts Maybe Text
_ -> Int -> TySyn name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
p TySyn name
ts
SigPropSyn PropSyn name
ps Maybe Text
_ -> Int -> PropSyn name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
p PropSyn name
ps
instance (Show name, PPName name) => PP (ModParam name) where
ppPrec :: Int -> ModParam name -> Doc
ppPrec Int
_ ModParam name
mp = [Doc] -> Doc
vcat ( [Doc]
mbDoc
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [ Doc
"import interface" Doc -> Doc -> Doc
<+>
ImpName name -> Doc
forall a. PP a => a -> Doc
pp (Located (ImpName name) -> ImpName name
forall a. Located a -> a
thing (ModParam name -> Located (ImpName name)
forall name. ModParam name -> Located (ImpName name)
mpSignature ModParam name
mp)) Doc -> Doc -> Doc
<+> Doc
mbAs ]
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc]
mbRen
)
where
mbDoc :: [Doc]
mbDoc = case ModParam name -> Maybe (Located Text)
forall name. ModParam name -> Maybe (Located Text)
mpDoc ModParam name
mp of
Maybe (Located Text)
Nothing -> []
Just Located Text
d -> [Located Text -> Doc
forall a. PP a => a -> Doc
pp Located Text
d]
mbAs :: Doc
mbAs = case ModParam name -> Maybe ModName
forall name. ModParam name -> Maybe ModName
mpAs ModParam name
mp of
Maybe ModName
Nothing -> Doc
forall a. Monoid a => a
mempty
Just ModName
d -> Doc
"as" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
d
mbRen :: [Doc]
mbRen
| Map name name -> Bool
forall k a. Map k a -> Bool
Map.null (ModParam name -> Map name name
forall name. ModParam name -> Map name name
mpRenaming ModParam name
mp) = []
| Bool
otherwise =
[ Int -> Doc -> Doc
indent Int
2 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ Doc
"/* Parameters"
Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: [ Doc
" *" Doc -> Doc -> Doc
<+> name -> Doc
forall a. PP a => a -> Doc
pp name
x Doc -> Doc -> Doc
<+> Doc
"->" Doc -> Doc -> Doc
<+> name -> Doc
forall a. PP a => a -> Doc
pp name
y
| (name
x,name
y) <- Map name name -> [(name, name)]
forall k a. Map k a -> [(k, a)]
Map.toList (ModParam name -> Map name name
forall name. ModParam name -> Map name name
mpRenaming ModParam name
mp) ]
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc
" */"] ]
instance (Show name, PPName name) => PP (PrimType name) where
ppPrec :: Int -> PrimType name -> Doc
ppPrec Int
_ PrimType name
pt =
Doc
"primitive" Doc -> Doc -> Doc
<+> Doc
"type" Doc -> Doc -> Doc
<+> Located name -> Doc
forall a. PP a => a -> Doc
pp (PrimType name -> Located name
forall name. PrimType name -> Located name
primTName PrimType name
pt) Doc -> Doc -> Doc
<+> Doc
":" Doc -> Doc -> Doc
<+> Located Kind -> Doc
forall a. PP a => a -> Doc
pp (PrimType name -> Located Kind
forall name. PrimType name -> Located Kind
primTKind PrimType name
pt)
instance (Show name, PPName name) => PP (ParameterType name) where
ppPrec :: Int -> ParameterType name -> Doc
ppPrec Int
_ ParameterType name
a = String -> Doc
text String
"type" Doc -> Doc -> Doc
<+>
Located name -> Doc
forall a. PPName a => a -> Doc
ppPrefixName (ParameterType name -> Located name
forall name. ParameterType name -> Located name
ptName ParameterType name
a) Doc -> Doc -> Doc
<+> String -> Doc
text String
":" Doc -> Doc -> Doc
<+> Kind -> Doc
forall a. PP a => a -> Doc
pp (ParameterType name -> Kind
forall name. ParameterType name -> Kind
ptKind ParameterType name
a)
instance (Show name, PPName name) => PP (ParameterFun name) where
ppPrec :: Int -> ParameterFun name -> Doc
ppPrec Int
_ ParameterFun name
a = Located name -> Doc
forall a. PPName a => a -> Doc
ppPrefixName (ParameterFun name -> Located name
forall name. ParameterFun name -> Located name
pfName ParameterFun name
a) Doc -> Doc -> Doc
<+> String -> Doc
text String
":"
Doc -> Doc -> Doc
<+> Schema name -> Doc
forall a. PP a => a -> Doc
pp (ParameterFun name -> Schema name
forall name. ParameterFun name -> Schema name
pfSchema ParameterFun name
a)
instance (Show name, PPName name) => PP (ParameterConstraint name) where
ppPrec :: Int -> ParameterConstraint name -> Doc
ppPrec Int
_ ParameterConstraint name
a = Doc
"type constraint" Doc -> Doc -> Doc
<+> Doc -> Doc
parens ([Doc] -> Doc
commaSep ((Located (Prop name) -> Doc) -> [Located (Prop name)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Prop name -> Doc
forall a. PP a => a -> Doc
pp (Prop name -> Doc)
-> (Located (Prop name) -> Prop name) -> Located (Prop name) -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located (Prop name) -> Prop name
forall a. Located a -> a
thing) (ParameterConstraint name -> [Located (Prop name)]
forall name. ParameterConstraint name -> [Located (Prop name)]
pcProps ParameterConstraint name
a)))
instance (Show name, PPName name) => PP (Decl name) where
ppPrec :: Int -> Decl name -> Doc
ppPrec Int
n Decl name
decl =
case Decl name
decl of
DSignature [Located name]
xs Schema name
s -> [Doc] -> Doc
commaSep ((Located name -> Doc) -> [Located name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Located name -> Doc
forall a. PP a => Located a -> Doc
ppL [Located name]
xs) Doc -> Doc -> Doc
<+> String -> Doc
text String
":" Doc -> Doc -> Doc
<+> Schema name -> Doc
forall a. PP a => a -> Doc
pp Schema name
s
DPatBind Pattern name
p Expr name
e -> Pattern name -> Doc
forall a. PP a => a -> Doc
pp Pattern name
p Doc -> Doc -> Doc
<+> String -> Doc
text String
"=" Doc -> Doc -> Doc
<+> Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e
DBind Bind name
b -> Int -> Bind name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
n Bind name
b
DRec [Bind name]
bs -> Int -> Doc -> Doc
nest Int
2 ([Doc] -> Doc
vcat (Doc
"recursive" Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: (Bind name -> Doc) -> [Bind name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Bind name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
n) [Bind name]
bs))
DFixity Fixity
f [Located name]
ns -> Fixity -> [Located name] -> Doc
forall name. PPName name => Fixity -> [Located name] -> Doc
ppFixity Fixity
f [Located name]
ns
DPragma [Located name]
xs Pragma
p -> [Located name] -> Pragma -> Doc
forall name. PPName name => [Located name] -> Pragma -> Doc
ppPragma [Located name]
xs Pragma
p
DType TySyn name
ts -> Int -> TySyn name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
n TySyn name
ts
DProp PropSyn name
ps -> Int -> PropSyn name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
n PropSyn name
ps
DLocated Decl name
d Range
_ -> Int -> Decl name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
n Decl name
d
ppFixity :: PPName name => Fixity -> [Located name] -> Doc
ppFixity :: forall name. PPName name => Fixity -> [Located name] -> Doc
ppFixity (Fixity Assoc
LeftAssoc Int
i) [Located name]
ns = String -> Doc
text String
"infixl" Doc -> Doc -> Doc
<+> Int -> Doc
int Int
i Doc -> Doc -> Doc
<+> [Doc] -> Doc
commaSep ((Located name -> Doc) -> [Located name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Located name -> Doc
forall a. PP a => a -> Doc
pp [Located name]
ns)
ppFixity (Fixity Assoc
RightAssoc Int
i) [Located name]
ns = String -> Doc
text String
"infixr" Doc -> Doc -> Doc
<+> Int -> Doc
int Int
i Doc -> Doc -> Doc
<+> [Doc] -> Doc
commaSep ((Located name -> Doc) -> [Located name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Located name -> Doc
forall a. PP a => a -> Doc
pp [Located name]
ns)
ppFixity (Fixity Assoc
NonAssoc Int
i) [Located name]
ns = String -> Doc
text String
"infix" Doc -> Doc -> Doc
<+> Int -> Doc
int Int
i Doc -> Doc -> Doc
<+> [Doc] -> Doc
commaSep ((Located name -> Doc) -> [Located name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Located name -> Doc
forall a. PP a => a -> Doc
pp [Located name]
ns)
instance PPName name => PP (Newtype name) where
ppPrec :: Int -> Newtype name -> Doc
ppPrec Int
_ Newtype name
nt = Int -> Doc -> Doc
nest Int
2 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
sep
[ [Doc] -> Doc
fsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ [String -> Doc
text String
"newtype", Located name -> Doc
forall a. PP a => Located a -> Doc
ppL (Newtype name -> Located name
forall name. Newtype name -> Located name
nName Newtype name
nt)] [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ (TParam name -> Doc) -> [TParam name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map TParam name -> Doc
forall a. PP a => a -> Doc
pp (Newtype name -> [TParam name]
forall name. Newtype name -> [TParam name]
nParams Newtype name
nt) [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Char -> Doc
char Char
'=']
, [Doc] -> Doc
ppRecord (((Ident, (Range, Type name)) -> Doc)
-> [(Ident, (Range, Type name))] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> (Ident, (Range, Type name)) -> Doc
forall a. PP a => String -> (Ident, (Range, a)) -> Doc
ppNamed' String
":") (RecordMap Ident (Range, Type name) -> [(Ident, (Range, Type name))]
forall a b. (Show a, Ord a) => RecordMap a b -> [(a, b)]
displayFields (Newtype name -> RecordMap Ident (Range, Type name)
forall name. Newtype name -> Rec (Type name)
nBody Newtype name
nt)))
]
instance (Show name, PPName name) => PP (EnumDecl name) where
ppPrec :: Int -> EnumDecl name -> Doc
ppPrec Int
_ EnumDecl name
ed = Int -> Doc -> Doc
nest Int
2 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
sep
[ [Doc] -> Doc
fsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ [String -> Doc
text String
"enum", Located name -> Doc
forall a. PP a => Located a -> Doc
ppL (EnumDecl name -> Located name
forall name. EnumDecl name -> Located name
eName EnumDecl name
ed)] [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ (TParam name -> Doc) -> [TParam name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map TParam name -> Doc
forall a. PP a => a -> Doc
pp (EnumDecl name -> [TParam name]
forall name. EnumDecl name -> [TParam name]
eParams EnumDecl name
ed) [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Char -> Doc
char Char
'=']
, [Doc] -> Doc
vcat [ Doc
pre Doc -> Doc -> Doc
<+> TopLevel (EnumCon name) -> Doc
forall a. PP a => a -> Doc
pp TopLevel (EnumCon name)
con | (Doc
pre, TopLevel (EnumCon name)
con) <- [Doc]
pres [Doc]
-> [TopLevel (EnumCon name)] -> [(Doc, TopLevel (EnumCon name))]
forall a b. [a] -> [b] -> [(a, b)]
`zip` EnumDecl name -> [TopLevel (EnumCon name)]
forall name. EnumDecl name -> [TopLevel (EnumCon name)]
eCons EnumDecl name
ed ]
]
where pres :: [Doc]
pres = Doc
" " Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: Doc -> [Doc]
forall a. a -> [a]
repeat Doc
"|"
instance (Show name, PPName name) => PP (EnumCon name) where
ppPrec :: Int -> EnumCon name -> Doc
ppPrec Int
_ EnumCon name
c = Located name -> Doc
forall a. PP a => a -> Doc
pp (EnumCon name -> Located name
forall name. EnumCon name -> Located name
ecName EnumCon name
c) Doc -> Doc -> Doc
<+> [Doc] -> Doc
hsep ((Type name -> Doc) -> [Type name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Type name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
1) (EnumCon name -> [Type name]
forall name. EnumCon name -> [Type name]
ecFields EnumCon name
c))
instance (PP mname) => PP (ImportG mname) where
ppPrec :: Int -> ImportG mname -> Doc
ppPrec Int
_ ImportG mname
d = [Doc] -> Doc
vcat [ String -> Doc
text String
"import" Doc -> Doc -> Doc
<+> [Doc] -> Doc
sep ([mname -> Doc
forall a. PP a => a -> Doc
pp (ImportG mname -> mname
forall mname. ImportG mname -> mname
iModule ImportG mname
d)] [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc]
mbInst [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++
[Doc]
mbAs [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc]
mbSpec)
, Int -> Doc -> Doc
indent Int
2 Doc
mbWhere
]
where
mbAs :: [Doc]
mbAs = [Doc] -> (ModName -> [Doc]) -> Maybe ModName -> [Doc]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\ ModName
name -> [String -> Doc
text String
"as" Doc -> Doc -> Doc
<+> ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
name]) (ImportG mname -> Maybe ModName
forall mname. ImportG mname -> Maybe ModName
iAs ImportG mname
d)
mbSpec :: [Doc]
mbSpec = [Doc] -> (ImportSpec -> [Doc]) -> Maybe ImportSpec -> [Doc]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\ImportSpec
x -> [ImportSpec -> Doc
forall a. PP a => a -> Doc
pp ImportSpec
x]) (ImportG mname -> Maybe ImportSpec
forall mname. ImportG mname -> Maybe ImportSpec
iSpec ImportG mname
d)
mbInst :: [Doc]
mbInst = case ImportG mname -> Maybe (ModuleInstanceArgs PName)
forall mname. ImportG mname -> Maybe (ModuleInstanceArgs PName)
iInst ImportG mname
d of
Just (DefaultInstArg Located (ModuleInstanceArg PName)
x) -> [ Doc -> Doc
braces (ModuleInstanceArg PName -> Doc
forall a. PP a => a -> Doc
pp (Located (ModuleInstanceArg PName) -> ModuleInstanceArg PName
forall a. Located a -> a
thing Located (ModuleInstanceArg PName)
x)) ]
Just (NamedInstArgs [ModuleInstanceNamedArg PName]
xs) -> [ Doc -> Doc
braces ([Doc] -> Doc
commaSep ((ModuleInstanceNamedArg PName -> Doc)
-> [ModuleInstanceNamedArg PName] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ModuleInstanceNamedArg PName -> Doc
forall a. PP a => a -> Doc
pp [ModuleInstanceNamedArg PName]
xs)) ]
Maybe (ModuleInstanceArgs PName)
_ -> []
mbWhere :: Doc
mbWhere = case ImportG mname -> Maybe (ModuleInstanceArgs PName)
forall mname. ImportG mname -> Maybe (ModuleInstanceArgs PName)
iInst ImportG mname
d of
Just (DefaultInstAnonArg [TopDecl PName]
ds) ->
Doc
"where" Doc -> Doc -> Doc
$$ [Doc] -> Doc
vcat ((TopDecl PName -> Doc) -> [TopDecl PName] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map TopDecl PName -> Doc
forall a. PP a => a -> Doc
pp [TopDecl PName]
ds)
Maybe (ModuleInstanceArgs PName)
_ -> Doc
forall a. Monoid a => a
mempty
instance PP name => PP (ImpName name) where
ppPrec :: Int -> ImpName name -> Doc
ppPrec Int
_ ImpName name
nm =
case ImpName name
nm of
ImpTop ModName
x -> ModName -> Doc
forall a. PP a => a -> Doc
pp ModName
x
ImpNested name
x -> Doc
"submodule" Doc -> Doc -> Doc
<+> name -> Doc
forall a. PP a => a -> Doc
pp name
x
instance PP ImportSpec where
ppPrec :: Int -> ImportSpec -> Doc
ppPrec Int
_ ImportSpec
s = case ImportSpec
s of
Hiding [Ident]
names -> String -> Doc
text String
"hiding" Doc -> Doc -> Doc
<+> Doc -> Doc
parens ([Doc] -> Doc
commaSep ((Ident -> Doc) -> [Ident] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Ident -> Doc
forall a. PP a => a -> Doc
pp [Ident]
names))
Only [Ident]
names -> Doc -> Doc
parens ([Doc] -> Doc
commaSep ((Ident -> Doc) -> [Ident] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Ident -> Doc
forall a. PP a => a -> Doc
pp [Ident]
names))
instance PP a => PP (TopLevel a) where
ppPrec :: Int -> TopLevel a -> Doc
ppPrec Int
_ TopLevel a
tl = a -> Doc
forall a. PP a => a -> Doc
pp (TopLevel a -> a
forall a. TopLevel a -> a
tlValue TopLevel a
tl)
instance PP Pragma where
ppPrec :: Int -> Pragma -> Doc
ppPrec Int
_ (PragmaNote String
x) = String -> Doc
text String
x
ppPrec Int
_ Pragma
PragmaProperty = String -> Doc
text String
"property"
ppPragma :: PPName name => [Located name] -> Pragma -> Doc
ppPragma :: forall name. PPName name => [Located name] -> Pragma -> Doc
ppPragma [Located name]
xs Pragma
p =
String -> Doc
text String
"/*" Doc -> Doc -> Doc
<+> String -> Doc
text String
"pragma" Doc -> Doc -> Doc
<+> [Doc] -> Doc
commaSep ((Located name -> Doc) -> [Located name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Located name -> Doc
forall a. PP a => Located a -> Doc
ppL [Located name]
xs) Doc -> Doc -> Doc
<+> String -> Doc
text String
":" Doc -> Doc -> Doc
<+> Pragma -> Doc
forall a. PP a => a -> Doc
pp Pragma
p
Doc -> Doc -> Doc
<+> String -> Doc
text String
"*/"
instance (Show name, PPName name) => PP (Bind name) where
ppPrec :: Int -> Bind name -> Doc
ppPrec Int
_ Bind name
b = [Doc] -> Doc
vcat ([Doc]
sig [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [ [Located name] -> Pragma -> Doc
forall name. PPName name => [Located name] -> Pragma -> Doc
ppPragma [Located name
f] Pragma
p | Pragma
p <- Bind name -> [Pragma]
forall name. Bind name -> [Pragma]
bPragmas Bind name
b ] [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++
[Doc -> Int -> Doc -> Doc
hang (Doc
def Doc -> Doc -> Doc
<+> Doc
eq) Int
4 (BindDef name -> Doc
forall a. PP a => a -> Doc
pp (Located (BindDef name) -> BindDef name
forall a. Located a -> a
thing (Bind name -> Located (BindDef name)
forall name. Bind name -> Located (BindDef name)
bDef Bind name
b)))])
where def :: Doc
def | Bind name -> Bool
forall name. Bind name -> Bool
bInfix Bind name
b = Doc
lhsOp
| Bool
otherwise = Doc
lhs
f :: Located name
f = Bind name -> Located name
forall name. Bind name -> Located name
bName Bind name
b
sig :: [Doc]
sig = case Bind name -> Maybe (Schema name)
forall name. Bind name -> Maybe (Schema name)
bSignature Bind name
b of
Maybe (Schema name)
Nothing -> []
Just Schema name
s -> [Decl name -> Doc
forall a. PP a => a -> Doc
pp ([Located name] -> Schema name -> Decl name
forall name. [Located name] -> Schema name -> Decl name
DSignature [Located name
f] Schema name
s)]
eq :: Doc
eq = if Bind name -> Bool
forall name. Bind name -> Bool
bMono Bind name
b then String -> Doc
text String
":=" else String -> Doc
text String
"="
lhs :: Doc
lhs = [Doc] -> Doc
fsep (Located name -> Doc
forall a. PP a => Located a -> Doc
ppL Located name
f Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: ((Pattern name -> Doc) -> [Pattern name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Pattern name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
3) (Bind name -> [Pattern name]
forall name. Bind name -> [Pattern name]
bindParams Bind name
b)))
lhsOp :: Doc
lhsOp = case Bind name -> [Pattern name]
forall name. Bind name -> [Pattern name]
bindParams Bind name
b of
[Pattern name
x,Pattern name
y] -> Pattern name -> Doc
forall a. PP a => a -> Doc
pp Pattern name
x Doc -> Doc -> Doc
<+> Located name -> Doc
forall a. PP a => Located a -> Doc
ppL Located name
f Doc -> Doc -> Doc
<+> Pattern name -> Doc
forall a. PP a => a -> Doc
pp Pattern name
y
[Pattern name]
xs -> Doc -> Doc
parens (Doc -> Doc
parens (Located name -> Doc
forall a. PP a => Located a -> Doc
ppL Located name
f) Doc -> Doc -> Doc
<+> [Doc] -> Doc
fsep ((Pattern name -> Doc) -> [Pattern name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Pattern name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
0) [Pattern name]
xs))
instance (Show name, PPName name) => PP (BindDef name) where
ppPrec :: Int -> BindDef name -> Doc
ppPrec Int
_ BindDef name
DPrim = String -> Doc
text String
"<primitive>"
ppPrec Int
p (DForeign Maybe (BindImpl name)
mi) = case Maybe (BindImpl name)
mi of
Just BindImpl name
i -> Doc
"(foreign)" Doc -> Doc -> Doc
<+> Int -> BindImpl name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
p BindImpl name
i
Maybe (BindImpl name)
Nothing -> Doc
"<foreign>"
ppPrec Int
p (DImpl BindImpl name
i) = Int -> BindImpl name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
p BindImpl name
i
instance (Show name, PPName name) => PP (BindImpl name) where
ppPrec :: Int -> BindImpl name -> Doc
ppPrec Int
p (DExpr Expr name
e) = Int -> Expr name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
p Expr name
e
ppPrec Int
_p (DPropGuards [PropGuardCase name]
_guards) = String -> Doc
text String
"propguards"
instance PPName name => PP (TySyn name) where
ppPrec :: Int -> TySyn name -> Doc
ppPrec Int
_ (TySyn Located name
x Maybe Fixity
_ [TParam name]
xs Type name
t) =
Int -> Doc -> Doc
nest Int
2 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
sep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$
[ [Doc] -> Doc
fsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ [String -> Doc
text String
"type", Located name -> Doc
forall a. PP a => Located a -> Doc
ppL Located name
x] [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ (TParam name -> Doc) -> [TParam name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> TParam name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
1) [TParam name]
xs [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [String -> Doc
text String
"="]
, Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t
]
instance PPName name => PP (PropSyn name) where
ppPrec :: Int -> PropSyn name -> Doc
ppPrec Int
_ (PropSyn Located name
x Maybe Fixity
_ [TParam name]
xs [Prop name]
ps) =
Int -> Doc -> Doc
nest Int
2 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
sep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$
[ [Doc] -> Doc
fsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ [String -> Doc
text String
"constraint", Located name -> Doc
forall a. PP a => Located a -> Doc
ppL Located name
x] [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ (TParam name -> Doc) -> [TParam name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> TParam name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
1) [TParam name]
xs [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [String -> Doc
text String
"="]
, Doc -> Doc
parens ([Doc] -> Doc
commaSep ((Prop name -> Doc) -> [Prop name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Prop name -> Doc
forall a. PP a => a -> Doc
pp [Prop name]
ps))
]
instance PP Literal where
ppPrec :: Int -> Literal -> Doc
ppPrec Int
_ Literal
lit =
case Literal
lit of
ECNum Integer
n NumInfo
i -> Integer -> NumInfo -> Doc
ppNumLit Integer
n NumInfo
i
ECChar Char
c -> String -> Doc
text (Char -> String
forall a. Show a => a -> String
show Char
c)
ECFrac Rational
n FracInfo
i -> Rational -> FracInfo -> Doc
ppFracLit Rational
n FracInfo
i
ECString String
s -> String -> Doc
text (ShowS
forall a. Show a => a -> String
show String
s)
ppFracLit :: Rational -> FracInfo -> Doc
ppFracLit :: Rational -> FracInfo -> Doc
ppFracLit Rational
x FracInfo
i
| Double -> Rational
forall a. Real a => a -> Rational
toRational Double
dbl Rational -> Rational -> Bool
forall a. Eq a => a -> a -> Bool
== Rational
x =
case FracInfo
i of
BinFrac Text
_ -> Doc
frac
OctFrac Text
_ -> Doc
frac
DecFrac Text
_ -> String -> Doc
text (Double -> ShowS
forall a. RealFloat a => a -> ShowS
showFloat Double
dbl String
"")
HexFrac Text
_ -> String -> Doc
text (Double -> ShowS
forall a. RealFloat a => a -> ShowS
showHFloat Double
dbl String
"")
| Bool
otherwise = Doc
frac
where
dbl :: Double
dbl = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
x :: Double
frac :: Doc
frac = Doc
"fraction`" Doc -> Doc -> Doc
<.> Doc -> Doc
braces
([Doc] -> Doc
commaSep ((Integer -> Doc) -> [Integer] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> Doc
integer [ Rational -> Integer
forall a. Ratio a -> a
numerator Rational
x, Rational -> Integer
forall a. Ratio a -> a
denominator Rational
x ]))
ppNumLit :: Integer -> NumInfo -> Doc
ppNumLit :: Integer -> NumInfo -> Doc
ppNumLit Integer
n NumInfo
info =
case NumInfo
info of
DecLit Text
_ -> Integer -> Doc
integer Integer
n
BinLit Text
_ Int
w -> Integer -> String -> Int -> Doc
pad Integer
2 String
"0b" Int
w
OctLit Text
_ Int
w -> Integer -> String -> Int -> Doc
pad Integer
8 String
"0o" Int
w
HexLit Text
_ Int
w -> Integer -> String -> Int -> Doc
pad Integer
16 String
"0x" Int
w
PolyLit Int
w -> String -> Doc
text String
"<|" Doc -> Doc -> Doc
<+> Int -> Doc
poly Int
w Doc -> Doc -> Doc
<+> String -> Doc
text String
"|>"
where
pad :: Integer -> String -> Int -> Doc
pad Integer
base String
pref Int
w =
let txt :: String
txt = Integer -> (Int -> Char) -> Integer -> ShowS
forall a. Integral a => a -> (Int -> Char) -> a -> ShowS
showIntAtBase Integer
base (String
"0123456789abcdef" String -> Int -> Char
forall a. HasCallStack => [a] -> Int -> a
!!) Integer
n String
""
in String -> Doc
text String
pref Doc -> Doc -> Doc
<.> String -> Doc
text (Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
txt) Char
'0') Doc -> Doc -> Doc
<.> String -> Doc
text String
txt
poly :: Int -> Doc
poly Int
w = let ([Int]
res,Maybe Int
deg) = Maybe Int -> [Int] -> Int -> Integer -> ([Int], Maybe Int)
forall {t} {a}.
(Integral t, Num a, Bits t) =>
Maybe a -> [a] -> a -> t -> ([a], Maybe a)
bits Maybe Int
forall a. Maybe a
Nothing [] Int
0 Integer
n
z :: [Doc]
z | Int
w Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = []
| Just Int
d <- Maybe Int
deg, Int
d Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
w = []
| Bool
otherwise = [Int -> Doc
polyTerm0 (Int
wInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)]
in [Doc] -> Doc
fsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
intersperse (String -> Doc
text String
"+") ([Doc] -> [Doc]) -> [Doc] -> [Doc]
forall a b. (a -> b) -> a -> b
$ [Doc]
z [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ (Int -> Doc) -> [Int] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Doc
polyTerm [Int]
res
polyTerm :: Int -> Doc
polyTerm Int
0 = String -> Doc
text String
"1"
polyTerm Int
1 = String -> Doc
text String
"x"
polyTerm Int
p = String -> Doc
text String
"x" Doc -> Doc -> Doc
<.> String -> Doc
text String
"^^" Doc -> Doc -> Doc
<.> Int -> Doc
int Int
p
polyTerm0 :: Int -> Doc
polyTerm0 Int
0 = String -> Doc
text String
"0"
polyTerm0 Int
p = String -> Doc
text String
"0" Doc -> Doc -> Doc
<.> String -> Doc
text String
"*" Doc -> Doc -> Doc
<.> Int -> Doc
polyTerm Int
p
bits :: Maybe a -> [a] -> a -> t -> ([a], Maybe a)
bits Maybe a
d [a]
res a
p t
num
| t
num t -> t -> Bool
forall a. Eq a => a -> a -> Bool
== t
0 = ([a]
res,Maybe a
d)
| t -> Bool
forall a. Integral a => a -> Bool
even t
num = Maybe a -> [a] -> a -> t -> ([a], Maybe a)
bits Maybe a
d [a]
res (a
p a -> a -> a
forall a. Num a => a -> a -> a
+ a
1) (t
num t -> Int -> t
forall a. Bits a => a -> Int -> a
`shiftR` Int
1)
| Bool
otherwise = Maybe a -> [a] -> a -> t -> ([a], Maybe a)
bits (a -> Maybe a
forall a. a -> Maybe a
Just a
p) (a
p a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
res) (a
p a -> a -> a
forall a. Num a => a -> a -> a
+ a
1) (t
num t -> Int -> t
forall a. Bits a => a -> Int -> a
`shiftR` Int
1)
wrap :: Int -> Int -> Doc -> Doc
wrap :: Int -> Int -> Doc -> Doc
wrap Int
contextPrec Int
myPrec Doc
doc = Bool -> Doc -> Doc
optParens (Int
myPrec Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
contextPrec) Doc
doc
isEApp :: Expr n -> Maybe (Expr n, Expr n)
isEApp :: forall n. Expr n -> Maybe (Expr n, Expr n)
isEApp (ELocated Expr n
e Range
_) = Expr n -> Maybe (Expr n, Expr n)
forall n. Expr n -> Maybe (Expr n, Expr n)
isEApp Expr n
e
isEApp (EApp Expr n
e1 Expr n
e2) = (Expr n, Expr n) -> Maybe (Expr n, Expr n)
forall a. a -> Maybe a
Just (Expr n
e1,Expr n
e2)
isEApp Expr n
_ = Maybe (Expr n, Expr n)
forall a. Maybe a
Nothing
asEApps :: Expr n -> (Expr n, [Expr n])
asEApps :: forall n. Expr n -> (Expr n, [Expr n])
asEApps Expr n
expr = Expr n -> [Expr n] -> (Expr n, [Expr n])
forall {n}. Expr n -> [Expr n] -> (Expr n, [Expr n])
go Expr n
expr []
where go :: Expr n -> [Expr n] -> (Expr n, [Expr n])
go Expr n
e [Expr n]
es = case Expr n -> Maybe (Expr n, Expr n)
forall n. Expr n -> Maybe (Expr n, Expr n)
isEApp Expr n
e of
Maybe (Expr n, Expr n)
Nothing -> (Expr n
e, [Expr n]
es)
Just (Expr n
e1, Expr n
e2) -> Expr n -> [Expr n] -> (Expr n, [Expr n])
go Expr n
e1 (Expr n
e2 Expr n -> [Expr n] -> [Expr n]
forall a. a -> [a] -> [a]
: [Expr n]
es)
instance PPName name => PP (TypeInst name) where
ppPrec :: Int -> TypeInst name -> Doc
ppPrec Int
_ (PosInst Type name
t) = Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t
ppPrec Int
_ (NamedInst Named (Type name)
x) = String -> Named (Type name) -> Doc
forall a. PP a => String -> Named a -> Doc
ppNamed String
"=" Named (Type name)
x
instance (Show name, PPName name) => PP (Expr name) where
ppPrec :: Int -> Expr name -> Doc
ppPrec Int
n Expr name
expr =
case Expr name
expr of
EVar name
x -> name -> Doc
forall a. PPName a => a -> Doc
ppPrefixName name
x
ELit Literal
x -> Literal -> Doc
forall a. PP a => a -> Doc
pp Literal
x
EGenerate Expr name
x -> Int -> Int -> Doc -> Doc
wrap Int
n Int
3 (String -> Doc
text String
"generate" Doc -> Doc -> Doc
<+> Int -> Expr name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
4 Expr name
x)
ETuple [Expr name]
es -> Doc -> Doc
parens ([Doc] -> Doc
commaSep ((Expr name -> Doc) -> [Expr name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Expr name -> Doc
forall a. PP a => a -> Doc
pp [Expr name]
es))
ERecord Rec (Expr name)
fs -> Doc -> Doc
braces ([Doc] -> Doc
commaSep (((Ident, (Range, Expr name)) -> Doc)
-> [(Ident, (Range, Expr name))] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> (Ident, (Range, Expr name)) -> Doc
forall a. PP a => String -> (Ident, (Range, a)) -> Doc
ppNamed' String
"=") (Rec (Expr name) -> [(Ident, (Range, Expr name))]
forall a b. (Show a, Ord a) => RecordMap a b -> [(a, b)]
displayFields Rec (Expr name)
fs)))
EList [Expr name]
es -> Doc -> Doc
brackets ([Doc] -> Doc
commaSep ((Expr name -> Doc) -> [Expr name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Expr name -> Doc
forall a. PP a => a -> Doc
pp [Expr name]
es))
EFromTo Type name
e1 Maybe (Type name)
e2 Type name
e3 Maybe (Type name)
t1 -> Doc -> Doc
brackets (Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e1 Doc -> Doc -> Doc
<.> Doc
step Doc -> Doc -> Doc
<+> String -> Doc
text String
".." Doc -> Doc -> Doc
<+> Doc
end)
where step :: Doc
step = Doc -> (Type name -> Doc) -> Maybe (Type name) -> Doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Doc
forall a. Monoid a => a
mempty (\Type name
e -> Doc
comma Doc -> Doc -> Doc
<+> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e) Maybe (Type name)
e2
end :: Doc
end = Doc -> (Type name -> Doc) -> Maybe (Type name) -> Doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e3) (\Type name
t -> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e3 Doc -> Doc -> Doc
<+> Doc
colon Doc -> Doc -> Doc
<+> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t) Maybe (Type name)
t1
EFromToBy Bool
isStrict Type name
e1 Type name
e2 Type name
e3 Maybe (Type name)
t1 -> Doc -> Doc
brackets (Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e1 Doc -> Doc -> Doc
<+> Doc
dots Doc -> Doc -> Doc
<+> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e2 Doc -> Doc -> Doc
<+> String -> Doc
text String
"by" Doc -> Doc -> Doc
<+> Doc
end)
where end :: Doc
end = Doc -> (Type name -> Doc) -> Maybe (Type name) -> Doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e3) (\Type name
t -> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e3 Doc -> Doc -> Doc
<+> Doc
colon Doc -> Doc -> Doc
<+> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t) Maybe (Type name)
t1
dots :: Doc
dots | Bool
isStrict = String -> Doc
text String
".. <"
| Bool
otherwise = String -> Doc
text String
".."
EFromToDownBy Bool
isStrict Type name
e1 Type name
e2 Type name
e3 Maybe (Type name)
t1 -> Doc -> Doc
brackets (Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e1 Doc -> Doc -> Doc
<+> Doc
dots Doc -> Doc -> Doc
<+> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e2 Doc -> Doc -> Doc
<+> String -> Doc
text String
"down by" Doc -> Doc -> Doc
<+> Doc
end)
where end :: Doc
end = Doc -> (Type name -> Doc) -> Maybe (Type name) -> Doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e3) (\Type name
t -> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e3 Doc -> Doc -> Doc
<+> Doc
colon Doc -> Doc -> Doc
<+> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t) Maybe (Type name)
t1
dots :: Doc
dots | Bool
isStrict = String -> Doc
text String
".. >"
| Bool
otherwise = String -> Doc
text String
".."
EFromToLessThan Type name
e1 Type name
e2 Maybe (Type name)
t1 -> Doc -> Doc
brackets (Doc
strt Doc -> Doc -> Doc
<+> String -> Doc
text String
".. <" Doc -> Doc -> Doc
<+> Doc
end)
where strt :: Doc
strt = Doc -> (Type name -> Doc) -> Maybe (Type name) -> Doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e1) (\Type name
t -> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e1 Doc -> Doc -> Doc
<+> Doc
colon Doc -> Doc -> Doc
<+> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t) Maybe (Type name)
t1
end :: Doc
end = Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
e2
EInfFrom Expr name
e1 Maybe (Expr name)
e2 -> Doc -> Doc
brackets (Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e1 Doc -> Doc -> Doc
<.> Doc
step Doc -> Doc -> Doc
<+> String -> Doc
text String
"...")
where step :: Doc
step = Doc -> (Expr name -> Doc) -> Maybe (Expr name) -> Doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Doc
forall a. Monoid a => a
mempty (\Expr name
e -> Doc
comma Doc -> Doc -> Doc
<+> Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e) Maybe (Expr name)
e2
EComp Expr name
e [[Match name]]
mss -> Doc -> Doc
brackets (Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc -> Doc
align ([Doc] -> Doc
vcat (([Match name] -> Doc) -> [[Match name]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map [Match name] -> Doc
forall {a}. PP a => [a] -> Doc
arm [[Match name]]
mss)))
where arm :: [a] -> Doc
arm [a]
ms = String -> Doc
text String
" |" Doc -> Doc -> Doc
<+> [Doc] -> Doc
commaSep ((a -> Doc) -> [a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map a -> Doc
forall a. PP a => a -> Doc
pp [a]
ms)
EUpd Maybe (Expr name)
mb [UpdField name]
fs -> Doc -> Doc
braces (Doc
hd Doc -> Doc -> Doc
<+> Doc
"|" Doc -> Doc -> Doc
<+> [Doc] -> Doc
commaSep ((UpdField name -> Doc) -> [UpdField name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map UpdField name -> Doc
forall a. PP a => a -> Doc
pp [UpdField name]
fs))
where hd :: Doc
hd = Doc -> (Expr name -> Doc) -> Maybe (Expr name) -> Doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Doc
"_" Expr name -> Doc
forall a. PP a => a -> Doc
pp Maybe (Expr name)
mb
ETypeVal Type name
t -> String -> Doc
text String
"`" Doc -> Doc -> Doc
<.> Int -> Type name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
5 Type name
t
EAppT Expr name
e [TypeInst name]
ts -> Int -> Expr name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
4 Expr name
e Doc -> Doc -> Doc
<.> String -> Doc
text String
"`" Doc -> Doc -> Doc
<.> Doc -> Doc
braces ([Doc] -> Doc
commaSep ((TypeInst name -> Doc) -> [TypeInst name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map TypeInst name -> Doc
forall a. PP a => a -> Doc
pp [TypeInst name]
ts))
ESel Expr name
e Selector
l -> Int -> Expr name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
4 Expr name
e Doc -> Doc -> Doc
<.> String -> Doc
text String
"." Doc -> Doc -> Doc
<.> Selector -> Doc
forall a. PP a => a -> Doc
pp Selector
l
EFun FunDesc name
_ [Pattern name]
xs Expr name
e -> Int -> Int -> Doc -> Doc
wrap Int
n Int
0 ((String -> Doc
text String
"\\" Doc -> Doc -> Doc
<.> [Doc] -> Doc
hsep ((Pattern name -> Doc) -> [Pattern name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Pattern name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
3) [Pattern name]
xs)) Doc -> Doc -> Doc
<+>
String -> Doc
text String
"->" Doc -> Doc -> Doc
<+> Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e)
EIf Expr name
e1 Expr name
e2 Expr name
e3 -> Int -> Int -> Doc -> Doc
wrap Int
n Int
0 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
sep [ String -> Doc
text String
"if" Doc -> Doc -> Doc
<+> Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e1
, String -> Doc
text String
"then" Doc -> Doc -> Doc
<+> Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e2
, String -> Doc
text String
"else" Doc -> Doc -> Doc
<+> Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e3 ]
ECase Expr name
e [CaseAlt name]
as -> Int -> Int -> Doc -> Doc
wrap Int
n Int
0 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vcat [ Doc
"case" Doc -> Doc -> Doc
<+> Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e Doc -> Doc -> Doc
<+> Doc
"of"
, Int -> Doc -> Doc
nest Int
2 ([Doc] -> Doc
vcat ((CaseAlt name -> Doc) -> [CaseAlt name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map CaseAlt name -> Doc
forall a. PP a => a -> Doc
pp [CaseAlt name]
as))
]
ETyped Expr name
e Type name
t -> Int -> Int -> Doc -> Doc
wrap Int
n Int
0 (Int -> Expr name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
2 Expr name
e Doc -> Doc -> Doc
<+> String -> Doc
text String
":" Doc -> Doc -> Doc
<+> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t)
EWhere Expr name
e [Decl name]
ds -> Int -> Int -> Doc -> Doc
wrap Int
n Int
0 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc
align (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vsep
[ Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e
, Doc -> Int -> Doc -> Doc
hang Doc
"where" Int
2 ([Doc] -> Doc
vcat ((Decl name -> Doc) -> [Decl name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Decl name -> Doc
forall a. PP a => a -> Doc
pp [Decl name]
ds))
]
Expr name
_ | Just Infix name (Expr name)
ifix <- Expr name -> Maybe (Infix name (Expr name))
forall {op}. PPName op => Expr op -> Maybe (Infix op (Expr op))
isInfix Expr name
expr ->
Bool -> Doc -> Doc
optParens (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
2)
(Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Int
-> (Expr name -> Maybe (Infix name (Expr name)))
-> Infix name (Expr name)
-> Doc
forall thing op.
(PP thing, PP op) =>
Int -> (thing -> Maybe (Infix op thing)) -> Infix op thing -> Doc
ppInfix Int
2 Expr name -> Maybe (Infix name (Expr name))
forall {op}. PPName op => Expr op -> Maybe (Infix op (Expr op))
isInfix Infix name (Expr name)
ifix
EApp Expr name
_ Expr name
_ -> let (Expr name
e, [Expr name]
es) = Expr name -> (Expr name, [Expr name])
forall n. Expr n -> (Expr n, [Expr n])
asEApps Expr name
expr in
Int -> Int -> Doc -> Doc
wrap Int
n Int
3 (Int -> Expr name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
3 Expr name
e Doc -> Doc -> Doc
<+> [Doc] -> Doc
fsep ((Expr name -> Doc) -> [Expr name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Expr name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
4) [Expr name]
es))
ELocated Expr name
e Range
_ -> Int -> Expr name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
n Expr name
e
ESplit Expr name
e -> Int -> Int -> Doc -> Doc
wrap Int
n Int
3 (String -> Doc
text String
"splitAt" Doc -> Doc -> Doc
<+> Int -> Expr name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
4 Expr name
e)
EParens Expr name
e -> Doc -> Doc
parens (Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e)
EInfix Expr name
e1 Located name
op Fixity
_ Expr name
e2 -> Int -> Int -> Doc -> Doc
wrap Int
n Int
0 (Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e1 Doc -> Doc -> Doc
<+> name -> Doc
forall a. PPName a => a -> Doc
ppInfixName (Located name -> name
forall a. Located a -> a
thing Located name
op) Doc -> Doc -> Doc
<+> Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e2)
EPrefix PrefixOp
op Expr name
e -> Int -> Int -> Doc -> Doc
wrap Int
n Int
3 (String -> Doc
text (PrefixOp -> String
forall {a}. IsString a => PrefixOp -> a
prefixText PrefixOp
op) Doc -> Doc -> Doc
<.> Int -> Expr name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
4 Expr name
e)
where
isInfix :: Expr op -> Maybe (Infix op (Expr op))
isInfix (EApp (EApp (EVar op
ieOp) Expr op
ieLeft) Expr op
ieRight) = do
Fixity
ieFixity <- op -> Maybe Fixity
forall a. PPName a => a -> Maybe Fixity
ppNameFixity op
ieOp
Infix op (Expr op) -> Maybe (Infix op (Expr op))
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return Infix { op
Fixity
Expr op
ieOp :: op
ieLeft :: Expr op
ieRight :: Expr op
ieFixity :: Fixity
ieOp :: op
ieLeft :: Expr op
ieRight :: Expr op
ieFixity :: Fixity
.. }
isInfix Expr op
_ = Maybe (Infix op (Expr op))
forall a. Maybe a
Nothing
prefixText :: PrefixOp -> a
prefixText PrefixOp
PrefixNeg = a
"-"
prefixText PrefixOp
PrefixComplement = a
"~"
instance (Show name, PPName name) => PP (CaseAlt name) where
ppPrec :: Int -> CaseAlt name -> Doc
ppPrec Int
_ (CaseAlt Pattern name
p Expr name
e) = [Doc] -> Doc
vcat [ Pattern name -> Doc
forall a. PP a => a -> Doc
pp Pattern name
p Doc -> Doc -> Doc
<+> Doc
"->", Int -> Doc -> Doc
nest Int
2 (Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e) ]
instance (Show name, PPName name) => PP (UpdField name) where
ppPrec :: Int -> UpdField name -> Doc
ppPrec Int
_ (UpdField UpdHow
h [Located Selector]
xs Expr name
e) = [Selector] -> Doc
ppNestedSels ((Located Selector -> Selector) -> [Located Selector] -> [Selector]
forall a b. (a -> b) -> [a] -> [b]
map Located Selector -> Selector
forall a. Located a -> a
thing [Located Selector]
xs) Doc -> Doc -> Doc
<+> UpdHow -> Doc
forall a. PP a => a -> Doc
pp UpdHow
h Doc -> Doc -> Doc
<+> Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e
instance PP UpdHow where
ppPrec :: Int -> UpdHow -> Doc
ppPrec Int
_ UpdHow
h = case UpdHow
h of
UpdHow
UpdSet -> Doc
"="
UpdHow
UpdFun -> Doc
"->"
instance PPName name => PP (Pattern name) where
ppPrec :: Int -> Pattern name -> Doc
ppPrec Int
n Pattern name
pat =
case Pattern name
pat of
PVar Located name
x -> name -> Doc
forall a. PP a => a -> Doc
pp (Located name -> name
forall a. Located a -> a
thing Located name
x)
PCon Located name
c [Pattern name]
ps ->
case [Pattern name]
ps of
[] -> Located name -> Doc
forall a. PP a => a -> Doc
pp Located name
c
[Pattern name]
_ -> Int -> Int -> Doc -> Doc
wrap Int
n Int
1 (Located name -> Doc
forall a. PP a => a -> Doc
pp Located name
c Doc -> Doc -> Doc
<+> [Doc] -> Doc
hsep ((Pattern name -> Doc) -> [Pattern name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Pattern name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
1) [Pattern name]
ps))
Pattern name
PWild -> Char -> Doc
char Char
'_'
PTuple [Pattern name]
ps -> [Doc] -> Doc
ppTuple ((Pattern name -> Doc) -> [Pattern name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Pattern name -> Doc
forall a. PP a => a -> Doc
pp [Pattern name]
ps)
PRecord Rec (Pattern name)
fs -> [Doc] -> Doc
ppRecord (((Ident, (Range, Pattern name)) -> Doc)
-> [(Ident, (Range, Pattern name))] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> (Ident, (Range, Pattern name)) -> Doc
forall a. PP a => String -> (Ident, (Range, a)) -> Doc
ppNamed' String
"=") (Rec (Pattern name) -> [(Ident, (Range, Pattern name))]
forall a b. (Show a, Ord a) => RecordMap a b -> [(a, b)]
displayFields Rec (Pattern name)
fs))
PList [Pattern name]
ps -> [Doc] -> Doc
ppList ((Pattern name -> Doc) -> [Pattern name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Pattern name -> Doc
forall a. PP a => a -> Doc
pp [Pattern name]
ps)
PTyped Pattern name
p Type name
t -> Int -> Int -> Doc -> Doc
wrap Int
n Int
0 (Int -> Pattern name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
1 Pattern name
p Doc -> Doc -> Doc
<+> String -> Doc
text String
":" Doc -> Doc -> Doc
<+> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t)
PSplit Pattern name
p1 Pattern name
p2 -> Int -> Int -> Doc -> Doc
wrap Int
n Int
1 (Int -> Pattern name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
1 Pattern name
p1 Doc -> Doc -> Doc
<+> String -> Doc
text String
"#" Doc -> Doc -> Doc
<+> Int -> Pattern name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
1 Pattern name
p2)
PLocated Pattern name
p Range
_ -> Int -> Pattern name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
n Pattern name
p
instance (Show name, PPName name) => PP (Match name) where
ppPrec :: Int -> Match name -> Doc
ppPrec Int
_ (Match Pattern name
p Expr name
e) = Pattern name -> Doc
forall a. PP a => a -> Doc
pp Pattern name
p Doc -> Doc -> Doc
<+> String -> Doc
text String
"<-" Doc -> Doc -> Doc
<+> Expr name -> Doc
forall a. PP a => a -> Doc
pp Expr name
e
ppPrec Int
_ (MatchLet Bind name
b) = Bind name -> Doc
forall a. PP a => a -> Doc
pp Bind name
b
instance PPName name => PP (Schema name) where
ppPrec :: Int -> Schema name -> Doc
ppPrec Int
_ (Forall [TParam name]
xs [Prop name]
ps Type name
t Maybe Range
_) = [Doc] -> Doc
sep ([Doc]
vars [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc]
preds [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t])
where vars :: [Doc]
vars = case [TParam name]
xs of
[] -> []
[TParam name]
_ -> [Int -> Doc -> Doc
nest Int
1 (Doc -> Doc
braces ([Doc] -> Doc
commaSepFill ((TParam name -> Doc) -> [TParam name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map TParam name -> Doc
forall a. PP a => a -> Doc
pp [TParam name]
xs)))]
preds :: [Doc]
preds = case [Prop name]
ps of
[] -> []
[Prop name]
_ -> [Int -> Doc -> Doc
nest Int
1 (Doc -> Doc
parens ([Doc] -> Doc
commaSepFill ((Prop name -> Doc) -> [Prop name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Prop name -> Doc
forall a. PP a => a -> Doc
pp [Prop name]
ps))) Doc -> Doc -> Doc
<+> String -> Doc
text String
"=>"]
instance PP Kind where
ppPrec :: Int -> Kind -> Doc
ppPrec Int
_ Kind
KType = String -> Doc
text String
"*"
ppPrec Int
_ Kind
KNum = String -> Doc
text String
"#"
ppPrec Int
_ Kind
KProp = String -> Doc
text String
"@"
ppPrec Int
n (KFun Kind
k1 Kind
k2) = Int -> Int -> Doc -> Doc
wrap Int
n Int
1 (Int -> Kind -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
1 Kind
k1 Doc -> Doc -> Doc
<+> Doc
"->" Doc -> Doc -> Doc
<+> Int -> Kind -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
0 Kind
k2)
cppKind :: Kind -> Doc
cppKind :: Kind -> Doc
cppKind Kind
KType = String -> Doc
text String
"a value type"
cppKind Kind
KNum = String -> Doc
text String
"a numeric type"
cppKind Kind
KProp = String -> Doc
text String
"a constraint type"
cppKind (KFun {}) = String -> Doc
text String
"a type-constructor type"
instance PPName name => PP (TParam name) where
ppPrec :: Int -> TParam name -> Doc
ppPrec Int
n (TParam name
p Maybe Kind
Nothing Maybe Range
_) = Int -> name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
n name
p
ppPrec Int
n (TParam name
p (Just Kind
k) Maybe Range
_) = Int -> Int -> Doc -> Doc
wrap Int
n Int
1 (name -> Doc
forall a. PP a => a -> Doc
pp name
p Doc -> Doc -> Doc
<+> String -> Doc
text String
":" Doc -> Doc -> Doc
<+> Kind -> Doc
forall a. PP a => a -> Doc
pp Kind
k)
instance PPName name => PP (Type name) where
ppPrec :: Int -> Type name -> Doc
ppPrec Int
n Type name
ty =
case Type name
ty of
Type name
TWild -> String -> Doc
text String
"_"
TTuple [Type name]
ts -> Doc -> Doc
parens (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
commaSep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (Type name -> Doc) -> [Type name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Type name -> Doc
forall a. PP a => a -> Doc
pp [Type name]
ts
TTyApp [Named (Type name)]
fs -> Doc -> Doc
braces (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
commaSep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (Named (Type name) -> Doc) -> [Named (Type name)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Named (Type name) -> Doc
forall a. PP a => String -> Named a -> Doc
ppNamed String
" = ") [Named (Type name)]
fs
TRecord Rec (Type name)
fs -> Doc -> Doc
braces (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
commaSep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ ((Ident, (Range, Type name)) -> Doc)
-> [(Ident, (Range, Type name))] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> (Ident, (Range, Type name)) -> Doc
forall a. PP a => String -> (Ident, (Range, a)) -> Doc
ppNamed' String
":") (Rec (Type name) -> [(Ident, (Range, Type name))]
forall a b. (Show a, Ord a) => RecordMap a b -> [(a, b)]
displayFields Rec (Type name)
fs)
Type name
TBit -> String -> Doc
text String
"Bit"
TNum Integer
x -> Integer -> Doc
integer Integer
x
TChar Char
x -> String -> Doc
text (Char -> String
forall a. Show a => a -> String
show Char
x)
TSeq Type name
t1 Type name
TBit -> Doc -> Doc
brackets (Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t1)
TSeq Type name
t1 Type name
t2 -> Bool -> Doc -> Doc
optParens (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
3)
(Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Doc -> Doc
brackets (Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t1) Doc -> Doc -> Doc
<.> Int -> Type name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
3 Type name
t2
TUser name
f [] -> name -> Doc
forall a. PPName a => a -> Doc
ppPrefixName name
f
TUser name
f [Type name]
ts -> Bool -> Doc -> Doc
optParens (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
3)
(Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ name -> Doc
forall a. PPName a => a -> Doc
ppPrefixName name
f Doc -> Doc -> Doc
<+> [Doc] -> Doc
fsep ((Type name -> Doc) -> [Type name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Type name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
4) [Type name]
ts)
TFun Type name
t1 Type name
t2 -> Bool -> Doc -> Doc
optParens (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1)
(Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
sep [Int -> Type name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
2 Type name
t1 Doc -> Doc -> Doc
<+> String -> Doc
text String
"->", Int -> Type name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
1 Type name
t2]
TLocated Type name
t Range
_ -> Int -> Type name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
n Type name
t
TParens Type name
t Maybe Kind
mb -> Doc -> Doc
parens
case Maybe Kind
mb of
Maybe Kind
Nothing -> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t
Just Kind
k -> Type name -> Doc
forall a. PP a => a -> Doc
pp Type name
t Doc -> Doc -> Doc
<+> Doc
":" Doc -> Doc -> Doc
<+> Kind -> Doc
forall a. PP a => a -> Doc
pp Kind
k
TInfix Type name
t1 Located name
o Fixity
_ Type name
t2 -> Bool -> Doc -> Doc
optParens (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
2)
(Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
sep [Int -> Type name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
2 Type name
t1 Doc -> Doc -> Doc
<+> Located name -> Doc
forall a. PPName a => a -> Doc
ppInfixName Located name
o, Int -> Type name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
3 Type name
t2]
instance PPName name => PP (Prop name) where
ppPrec :: Int -> Prop name -> Doc
ppPrec Int
n (CType Type name
t) = Int -> Type name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
n Type name
t
instance PPName name => PP [Prop name] where
ppPrec :: Int -> [Prop name] -> Doc
ppPrec Int
n [Prop name]
props = Doc -> Doc
parens (Doc -> Doc) -> ([Prop name] -> Doc) -> [Prop name] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Doc] -> Doc
commaSep ([Doc] -> Doc) -> ([Prop name] -> [Doc]) -> [Prop name] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Prop name -> Doc) -> [Prop name] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Prop name -> Doc
forall a. PP a => Int -> a -> Doc
ppPrec Int
n) ([Prop name] -> Doc) -> [Prop name] -> Doc
forall a b. (a -> b) -> a -> b
$ [Prop name]
props
class NoPos t where
noPos :: t -> t
instance NoPos (Located t) where
noPos :: Located t -> Located t
noPos Located t
x = Located t
x { srcRange = rng }
where rng :: Range
rng = Range { from :: Position
from = Int -> Int -> Position
Position Int
0 Int
0, to :: Position
to = Int -> Int -> Position
Position Int
0 Int
0, source :: String
source = String
"" }
instance NoPos t => NoPos (Named t) where
noPos :: Named t -> Named t
noPos Named t
t = Named { name :: Located Ident
name = Located Ident -> Located Ident
forall t. NoPos t => t -> t
noPos (Named t -> Located Ident
forall a. Named a -> Located Ident
name Named t
t), value :: t
value = t -> t
forall t. NoPos t => t -> t
noPos (Named t -> t
forall a. Named a -> a
value Named t
t) }
instance NoPos Range where
noPos :: Range -> Range
noPos Range
_ = Range { from :: Position
from = Int -> Int -> Position
Position Int
0 Int
0, to :: Position
to = Int -> Int -> Position
Position Int
0 Int
0, source :: String
source = String
"" }
instance NoPos t => NoPos [t] where noPos :: [t] -> [t]
noPos = (t -> t) -> [t] -> [t]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t -> t
forall t. NoPos t => t -> t
noPos
instance NoPos t => NoPos (Maybe t) where noPos :: Maybe t -> Maybe t
noPos = (t -> t) -> Maybe t -> Maybe t
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t -> t
forall t. NoPos t => t -> t
noPos
instance (NoPos a, NoPos b) => NoPos (a,b) where
noPos :: (a, b) -> (a, b)
noPos (a
a,b
b) = (a -> a
forall t. NoPos t => t -> t
noPos a
a, b -> b
forall t. NoPos t => t -> t
noPos b
b)
instance NoPos (Program name) where
noPos :: Program name -> Program name
noPos (Program [TopDecl name]
x) = [TopDecl name] -> Program name
forall name. [TopDecl name] -> Program name
Program ([TopDecl name] -> [TopDecl name]
forall t. NoPos t => t -> t
noPos [TopDecl name]
x)
instance NoPos (ModuleG mname name) where
noPos :: ModuleG mname name -> ModuleG mname name
noPos ModuleG mname name
m = Module { mName :: Located mname
mName = ModuleG mname name -> Located mname
forall mname name. ModuleG mname name -> Located mname
mName ModuleG mname name
m
, mDef :: ModuleDefinition name
mDef = ModuleDefinition name -> ModuleDefinition name
forall t. NoPos t => t -> t
noPos (ModuleG mname name -> ModuleDefinition name
forall mname name. ModuleG mname name -> ModuleDefinition name
mDef ModuleG mname name
m)
, mInScope :: NamingEnv
mInScope = ModuleG mname name -> NamingEnv
forall mname name. ModuleG mname name -> NamingEnv
mInScope ModuleG mname name
m
, mDocTop :: Maybe (Located Text)
mDocTop = Maybe (Located Text) -> Maybe (Located Text)
forall t. NoPos t => t -> t
noPos (ModuleG mname name -> Maybe (Located Text)
forall mname name. ModuleG mname name -> Maybe (Located Text)
mDocTop ModuleG mname name
m)
}
instance NoPos (ModuleDefinition name) where
noPos :: ModuleDefinition name -> ModuleDefinition name
noPos ModuleDefinition name
m =
case ModuleDefinition name
m of
NormalModule [TopDecl name]
ds -> [TopDecl name] -> ModuleDefinition name
forall name. [TopDecl name] -> ModuleDefinition name
NormalModule ([TopDecl name] -> [TopDecl name]
forall t. NoPos t => t -> t
noPos [TopDecl name]
ds)
FunctorInstance Located (ImpName name)
f ModuleInstanceArgs name
as ModuleInstance name
ds -> Located (ImpName name)
-> ModuleInstanceArgs name
-> ModuleInstance name
-> ModuleDefinition name
forall name.
Located (ImpName name)
-> ModuleInstanceArgs name
-> ModuleInstance name
-> ModuleDefinition name
FunctorInstance (Located (ImpName name) -> Located (ImpName name)
forall t. NoPos t => t -> t
noPos Located (ImpName name)
f) (ModuleInstanceArgs name -> ModuleInstanceArgs name
forall t. NoPos t => t -> t
noPos ModuleInstanceArgs name
as) ModuleInstance name
ds
InterfaceModule Signature name
s -> Signature name -> ModuleDefinition name
forall name. Signature name -> ModuleDefinition name
InterfaceModule (Signature name -> Signature name
forall t. NoPos t => t -> t
noPos Signature name
s)
instance NoPos (ModuleInstanceArgs name) where
noPos :: ModuleInstanceArgs name -> ModuleInstanceArgs name
noPos ModuleInstanceArgs name
as =
case ModuleInstanceArgs name
as of
DefaultInstArg Located (ModuleInstanceArg name)
a -> Located (ModuleInstanceArg name) -> ModuleInstanceArgs name
forall name.
Located (ModuleInstanceArg name) -> ModuleInstanceArgs name
DefaultInstArg (Located (ModuleInstanceArg name)
-> Located (ModuleInstanceArg name)
forall t. NoPos t => t -> t
noPos Located (ModuleInstanceArg name)
a)
DefaultInstAnonArg [TopDecl name]
ds -> [TopDecl name] -> ModuleInstanceArgs name
forall name. [TopDecl name] -> ModuleInstanceArgs name
DefaultInstAnonArg ([TopDecl name] -> [TopDecl name]
forall t. NoPos t => t -> t
noPos [TopDecl name]
ds)
NamedInstArgs [ModuleInstanceNamedArg name]
xs -> [ModuleInstanceNamedArg name] -> ModuleInstanceArgs name
forall name.
[ModuleInstanceNamedArg name] -> ModuleInstanceArgs name
NamedInstArgs ([ModuleInstanceNamedArg name] -> [ModuleInstanceNamedArg name]
forall t. NoPos t => t -> t
noPos [ModuleInstanceNamedArg name]
xs)
instance NoPos (ModuleInstanceNamedArg name) where
noPos :: ModuleInstanceNamedArg name -> ModuleInstanceNamedArg name
noPos (ModuleInstanceNamedArg Located Ident
x Located (ModuleInstanceArg name)
y) =
Located Ident
-> Located (ModuleInstanceArg name) -> ModuleInstanceNamedArg name
forall name.
Located Ident
-> Located (ModuleInstanceArg name) -> ModuleInstanceNamedArg name
ModuleInstanceNamedArg (Located Ident -> Located Ident
forall t. NoPos t => t -> t
noPos Located Ident
x) (Located (ModuleInstanceArg name)
-> Located (ModuleInstanceArg name)
forall t. NoPos t => t -> t
noPos Located (ModuleInstanceArg name)
y)
instance NoPos (NestedModule name) where
noPos :: NestedModule name -> NestedModule name
noPos (NestedModule ModuleG name name
m) = ModuleG name name -> NestedModule name
forall name. ModuleG name name -> NestedModule name
NestedModule (ModuleG name name -> ModuleG name name
forall t. NoPos t => t -> t
noPos ModuleG name name
m)
instance NoPos (TopDecl name) where
noPos :: TopDecl name -> TopDecl name
noPos TopDecl name
decl =
case TopDecl name
decl of
Decl TopLevel (Decl name)
x -> TopLevel (Decl name) -> TopDecl name
forall name. TopLevel (Decl name) -> TopDecl name
Decl (TopLevel (Decl name) -> TopLevel (Decl name)
forall t. NoPos t => t -> t
noPos TopLevel (Decl name)
x)
DPrimType TopLevel (PrimType name)
t -> TopLevel (PrimType name) -> TopDecl name
forall name. TopLevel (PrimType name) -> TopDecl name
DPrimType (TopLevel (PrimType name) -> TopLevel (PrimType name)
forall t. NoPos t => t -> t
noPos TopLevel (PrimType name)
t)
TDNewtype TopLevel (Newtype name)
n -> TopLevel (Newtype name) -> TopDecl name
forall name. TopLevel (Newtype name) -> TopDecl name
TDNewtype(TopLevel (Newtype name) -> TopLevel (Newtype name)
forall t. NoPos t => t -> t
noPos TopLevel (Newtype name)
n)
TDEnum TopLevel (EnumDecl name)
n -> TopLevel (EnumDecl name) -> TopDecl name
forall name. TopLevel (EnumDecl name) -> TopDecl name
TDEnum (TopLevel (EnumDecl name) -> TopLevel (EnumDecl name)
forall t. NoPos t => t -> t
noPos TopLevel (EnumDecl name)
n)
Include Located String
x -> Located String -> TopDecl name
forall name. Located String -> TopDecl name
Include (Located String -> Located String
forall t. NoPos t => t -> t
noPos Located String
x)
DModule TopLevel (NestedModule name)
d -> TopLevel (NestedModule name) -> TopDecl name
forall name. TopLevel (NestedModule name) -> TopDecl name
DModule (TopLevel (NestedModule name) -> TopLevel (NestedModule name)
forall t. NoPos t => t -> t
noPos TopLevel (NestedModule name)
d)
DImport Located (ImportG (ImpName name))
x -> Located (ImportG (ImpName name)) -> TopDecl name
forall name. Located (ImportG (ImpName name)) -> TopDecl name
DImport (Located (ImportG (ImpName name))
-> Located (ImportG (ImpName name))
forall t. NoPos t => t -> t
noPos Located (ImportG (ImpName name))
x)
DModParam ModParam name
d -> ModParam name -> TopDecl name
forall name. ModParam name -> TopDecl name
DModParam (ModParam name -> ModParam name
forall t. NoPos t => t -> t
noPos ModParam name
d)
DParamDecl Range
_ Signature name
ds -> Range -> Signature name -> TopDecl name
forall name. Range -> Signature name -> TopDecl name
DParamDecl Range
rng (Signature name -> Signature name
forall t. NoPos t => t -> t
noPos Signature name
ds)
where rng :: Range
rng = Range { from :: Position
from = Int -> Int -> Position
Position Int
0 Int
0, to :: Position
to = Int -> Int -> Position
Position Int
0 Int
0, source :: String
source = String
"" }
DInterfaceConstraint Maybe (Located Text)
d Located [Prop name]
ds -> Maybe (Located Text) -> Located [Prop name] -> TopDecl name
forall name.
Maybe (Located Text) -> Located [Prop name] -> TopDecl name
DInterfaceConstraint Maybe (Located Text)
d (Located [Prop name] -> Located [Prop name]
forall t. NoPos t => t -> t
noPos ([Prop name] -> [Prop name]
forall t. NoPos t => t -> t
noPos ([Prop name] -> [Prop name])
-> Located [Prop name] -> Located [Prop name]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Located [Prop name]
ds))
instance NoPos (ParamDecl name) where
noPos :: ParamDecl name -> ParamDecl name
noPos ParamDecl name
pd =
case ParamDecl name
pd of
DParameterFun ParameterFun name
d -> ParameterFun name -> ParamDecl name
forall name. ParameterFun name -> ParamDecl name
DParameterFun (ParameterFun name -> ParameterFun name
forall t. NoPos t => t -> t
noPos ParameterFun name
d)
DParameterType ParameterType name
d -> ParameterType name -> ParamDecl name
forall name. ParameterType name -> ParamDecl name
DParameterType (ParameterType name -> ParameterType name
forall t. NoPos t => t -> t
noPos ParameterType name
d)
DParameterDecl SigDecl name
d -> SigDecl name -> ParamDecl name
forall name. SigDecl name -> ParamDecl name
DParameterDecl (SigDecl name -> SigDecl name
forall t. NoPos t => t -> t
noPos SigDecl name
d)
DParameterConstraint ParameterConstraint name
d -> ParameterConstraint name -> ParamDecl name
forall name. ParameterConstraint name -> ParamDecl name
DParameterConstraint (ParameterConstraint name -> ParameterConstraint name
forall t. NoPos t => t -> t
noPos ParameterConstraint name
d)
instance NoPos (Signature name) where
noPos :: Signature name -> Signature name
noPos Signature name
sig = Signature { sigImports :: [Located (ImportG (ImpName name))]
sigImports = Signature name -> [Located (ImportG (ImpName name))]
forall name. Signature name -> [Located (ImportG (ImpName name))]
sigImports Signature name
sig
, sigTypeParams :: [ParameterType name]
sigTypeParams = (ParameterType name -> ParameterType name)
-> [ParameterType name] -> [ParameterType name]
forall a b. (a -> b) -> [a] -> [b]
map ParameterType name -> ParameterType name
forall t. NoPos t => t -> t
noPos (Signature name -> [ParameterType name]
forall name. Signature name -> [ParameterType name]
sigTypeParams Signature name
sig)
, sigDecls :: [SigDecl name]
sigDecls = (SigDecl name -> SigDecl name) -> [SigDecl name] -> [SigDecl name]
forall a b. (a -> b) -> [a] -> [b]
map SigDecl name -> SigDecl name
forall t. NoPos t => t -> t
noPos (Signature name -> [SigDecl name]
forall name. Signature name -> [SigDecl name]
sigDecls Signature name
sig)
, sigConstraints :: [Located (Prop name)]
sigConstraints = (Located (Prop name) -> Located (Prop name))
-> [Located (Prop name)] -> [Located (Prop name)]
forall a b. (a -> b) -> [a] -> [b]
map Located (Prop name) -> Located (Prop name)
forall t. NoPos t => t -> t
noPos (Signature name -> [Located (Prop name)]
forall name. Signature name -> [Located (Prop name)]
sigConstraints Signature name
sig)
, sigFunParams :: [ParameterFun name]
sigFunParams = (ParameterFun name -> ParameterFun name)
-> [ParameterFun name] -> [ParameterFun name]
forall a b. (a -> b) -> [a] -> [b]
map ParameterFun name -> ParameterFun name
forall t. NoPos t => t -> t
noPos (Signature name -> [ParameterFun name]
forall name. Signature name -> [ParameterFun name]
sigFunParams Signature name
sig)
}
instance NoPos (SigDecl name) where
noPos :: SigDecl name -> SigDecl name
noPos SigDecl name
decl =
case SigDecl name
decl of
SigTySyn TySyn name
ts Maybe Text
mb -> TySyn name -> Maybe Text -> SigDecl name
forall name. TySyn name -> Maybe Text -> SigDecl name
SigTySyn (TySyn name -> TySyn name
forall t. NoPos t => t -> t
noPos TySyn name
ts) Maybe Text
mb
SigPropSyn PropSyn name
ps Maybe Text
mb -> PropSyn name -> Maybe Text -> SigDecl name
forall name. PropSyn name -> Maybe Text -> SigDecl name
SigPropSyn (PropSyn name -> PropSyn name
forall t. NoPos t => t -> t
noPos PropSyn name
ps) Maybe Text
mb
instance NoPos (ModParam name) where
noPos :: ModParam name -> ModParam name
noPos ModParam name
mp = ModParam { mpSignature :: Located (ImpName name)
mpSignature = Located (ImpName name) -> Located (ImpName name)
forall t. NoPos t => t -> t
noPos (ModParam name -> Located (ImpName name)
forall name. ModParam name -> Located (ImpName name)
mpSignature ModParam name
mp)
, mpAs :: Maybe ModName
mpAs = ModParam name -> Maybe ModName
forall name. ModParam name -> Maybe ModName
mpAs ModParam name
mp
, mpName :: Ident
mpName = ModParam name -> Ident
forall name. ModParam name -> Ident
mpName ModParam name
mp
, mpDoc :: Maybe (Located Text)
mpDoc = ModParam name -> Maybe (Located Text)
forall name. ModParam name -> Maybe (Located Text)
mpDoc ModParam name
mp
, mpRenaming :: Map name name
mpRenaming = ModParam name -> Map name name
forall name. ModParam name -> Map name name
mpRenaming ModParam name
mp
}
instance NoPos (PrimType name) where
noPos :: PrimType name -> PrimType name
noPos PrimType name
x = PrimType name
x
instance NoPos (ParameterType name) where
noPos :: ParameterType name -> ParameterType name
noPos ParameterType name
a = ParameterType name
a
instance NoPos (ParameterFun x) where
noPos :: ParameterFun x -> ParameterFun x
noPos ParameterFun x
x = ParameterFun x
x { pfSchema = noPos (pfSchema x) }
instance NoPos (ParameterConstraint x) where
noPos :: ParameterConstraint x -> ParameterConstraint x
noPos ParameterConstraint x
x = ParameterConstraint x
x { pcProps = noPos (pcProps x) }
instance NoPos a => NoPos (TopLevel a) where
noPos :: TopLevel a -> TopLevel a
noPos TopLevel a
tl = TopLevel a
tl { tlValue = noPos (tlValue tl) }
instance NoPos (Decl name) where
noPos :: Decl name -> Decl name
noPos Decl name
decl =
case Decl name
decl of
DSignature [Located name]
x Schema name
y -> [Located name] -> Schema name -> Decl name
forall name. [Located name] -> Schema name -> Decl name
DSignature ([Located name] -> [Located name]
forall t. NoPos t => t -> t
noPos [Located name]
x) (Schema name -> Schema name
forall t. NoPos t => t -> t
noPos Schema name
y)
DPragma [Located name]
x Pragma
y -> [Located name] -> Pragma -> Decl name
forall name. [Located name] -> Pragma -> Decl name
DPragma ([Located name] -> [Located name]
forall t. NoPos t => t -> t
noPos [Located name]
x) (Pragma -> Pragma
forall t. NoPos t => t -> t
noPos Pragma
y)
DPatBind Pattern name
x Expr name
y -> Pattern name -> Expr name -> Decl name
forall name. Pattern name -> Expr name -> Decl name
DPatBind (Pattern name -> Pattern name
forall t. NoPos t => t -> t
noPos Pattern name
x) (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
y)
DFixity Fixity
f [Located name]
ns -> Fixity -> [Located name] -> Decl name
forall name. Fixity -> [Located name] -> Decl name
DFixity Fixity
f ([Located name] -> [Located name]
forall t. NoPos t => t -> t
noPos [Located name]
ns)
DBind Bind name
x -> Bind name -> Decl name
forall name. Bind name -> Decl name
DBind (Bind name -> Bind name
forall t. NoPos t => t -> t
noPos Bind name
x)
DRec [Bind name]
bs -> [Bind name] -> Decl name
forall name. [Bind name] -> Decl name
DRec ((Bind name -> Bind name) -> [Bind name] -> [Bind name]
forall a b. (a -> b) -> [a] -> [b]
map Bind name -> Bind name
forall t. NoPos t => t -> t
noPos [Bind name]
bs)
DType TySyn name
x -> TySyn name -> Decl name
forall name. TySyn name -> Decl name
DType (TySyn name -> TySyn name
forall t. NoPos t => t -> t
noPos TySyn name
x)
DProp PropSyn name
x -> PropSyn name -> Decl name
forall name. PropSyn name -> Decl name
DProp (PropSyn name -> PropSyn name
forall t. NoPos t => t -> t
noPos PropSyn name
x)
DLocated Decl name
x Range
_ -> Decl name -> Decl name
forall t. NoPos t => t -> t
noPos Decl name
x
instance NoPos (Newtype name) where
noPos :: Newtype name -> Newtype name
noPos Newtype name
n = Newtype { nName :: Located name
nName = Located name -> Located name
forall t. NoPos t => t -> t
noPos (Newtype name -> Located name
forall name. Newtype name -> Located name
nName Newtype name
n)
, nParams :: [TParam name]
nParams = Newtype name -> [TParam name]
forall name. Newtype name -> [TParam name]
nParams Newtype name
n
, nConName :: name
nConName = Newtype name -> name
forall name. Newtype name -> name
nConName Newtype name
n
, nBody :: Rec (Type name)
nBody = ((Range, Type name) -> (Range, Type name))
-> Rec (Type name) -> Rec (Type name)
forall a b. (a -> b) -> RecordMap Ident a -> RecordMap Ident b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Range, Type name) -> (Range, Type name)
forall t. NoPos t => t -> t
noPos (Newtype name -> Rec (Type name)
forall name. Newtype name -> Rec (Type name)
nBody Newtype name
n)
}
instance NoPos (EnumDecl name) where
noPos :: EnumDecl name -> EnumDecl name
noPos EnumDecl name
n = EnumDecl { eName :: Located name
eName = Located name -> Located name
forall t. NoPos t => t -> t
noPos (EnumDecl name -> Located name
forall name. EnumDecl name -> Located name
eName EnumDecl name
n)
, eParams :: [TParam name]
eParams = EnumDecl name -> [TParam name]
forall name. EnumDecl name -> [TParam name]
eParams EnumDecl name
n
, eCons :: [TopLevel (EnumCon name)]
eCons = (TopLevel (EnumCon name) -> TopLevel (EnumCon name))
-> [TopLevel (EnumCon name)] -> [TopLevel (EnumCon name)]
forall a b. (a -> b) -> [a] -> [b]
map TopLevel (EnumCon name) -> TopLevel (EnumCon name)
forall t. NoPos t => t -> t
noPos (EnumDecl name -> [TopLevel (EnumCon name)]
forall name. EnumDecl name -> [TopLevel (EnumCon name)]
eCons EnumDecl name
n)
}
instance NoPos (EnumCon name) where
noPos :: EnumCon name -> EnumCon name
noPos EnumCon name
c = EnumCon { ecName :: Located name
ecName = Located name -> Located name
forall t. NoPos t => t -> t
noPos (EnumCon name -> Located name
forall name. EnumCon name -> Located name
ecName EnumCon name
c), ecFields :: [Type name]
ecFields = [Type name] -> [Type name]
forall t. NoPos t => t -> t
noPos (EnumCon name -> [Type name]
forall name. EnumCon name -> [Type name]
ecFields EnumCon name
c) }
instance NoPos (BindParams name) where
noPos :: BindParams name -> BindParams name
noPos BindParams name
bp = case BindParams name
bp of
PatternParams [Pattern name]
ps -> [Pattern name] -> BindParams name
forall name. [Pattern name] -> BindParams name
PatternParams ([Pattern name] -> [Pattern name]
forall t. NoPos t => t -> t
noPos [Pattern name]
ps)
DroppedParams Maybe Range
_ Int
i -> Maybe Range -> Int -> BindParams name
forall name. Maybe Range -> Int -> BindParams name
DroppedParams Maybe Range
forall a. Maybe a
Nothing Int
i
instance NoPos (Bind name) where
noPos :: Bind name -> Bind name
noPos Bind name
x = Bind { bName :: Located name
bName = Located name -> Located name
forall t. NoPos t => t -> t
noPos (Bind name -> Located name
forall name. Bind name -> Located name
bName Bind name
x)
, bParams :: BindParams name
bParams = BindParams name -> BindParams name
forall t. NoPos t => t -> t
noPos (Bind name -> BindParams name
forall name. Bind name -> BindParams name
bParams Bind name
x)
, bDef :: Located (BindDef name)
bDef = Located (BindDef name) -> Located (BindDef name)
forall t. NoPos t => t -> t
noPos (Bind name -> Located (BindDef name)
forall name. Bind name -> Located (BindDef name)
bDef Bind name
x)
, bSignature :: Maybe (Schema name)
bSignature = Maybe (Schema name) -> Maybe (Schema name)
forall t. NoPos t => t -> t
noPos (Bind name -> Maybe (Schema name)
forall name. Bind name -> Maybe (Schema name)
bSignature Bind name
x)
, bInfix :: Bool
bInfix = Bind name -> Bool
forall name. Bind name -> Bool
bInfix Bind name
x
, bFixity :: Maybe Fixity
bFixity = Bind name -> Maybe Fixity
forall name. Bind name -> Maybe Fixity
bFixity Bind name
x
, bPragmas :: [Pragma]
bPragmas = [Pragma] -> [Pragma]
forall t. NoPos t => t -> t
noPos (Bind name -> [Pragma]
forall name. Bind name -> [Pragma]
bPragmas Bind name
x)
, bMono :: Bool
bMono = Bind name -> Bool
forall name. Bind name -> Bool
bMono Bind name
x
, bDoc :: Maybe (Located Text)
bDoc = Bind name -> Maybe (Located Text)
forall name. Bind name -> Maybe (Located Text)
bDoc Bind name
x
, bExport :: ExportType
bExport = Bind name -> ExportType
forall name. Bind name -> ExportType
bExport Bind name
x
}
instance NoPos Pragma where
noPos :: Pragma -> Pragma
noPos p :: Pragma
p@(PragmaNote {}) = Pragma
p
noPos p :: Pragma
p@(Pragma
PragmaProperty) = Pragma
p
instance NoPos (TySyn name) where
noPos :: TySyn name -> TySyn name
noPos (TySyn Located name
x Maybe Fixity
f [TParam name]
y Type name
z) = Located name
-> Maybe Fixity -> [TParam name] -> Type name -> TySyn name
forall n.
Located n -> Maybe Fixity -> [TParam n] -> Type n -> TySyn n
TySyn (Located name -> Located name
forall t. NoPos t => t -> t
noPos Located name
x) Maybe Fixity
f ([TParam name] -> [TParam name]
forall t. NoPos t => t -> t
noPos [TParam name]
y) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
z)
instance NoPos (PropSyn name) where
noPos :: PropSyn name -> PropSyn name
noPos (PropSyn Located name
x Maybe Fixity
f [TParam name]
y [Prop name]
z) = Located name
-> Maybe Fixity -> [TParam name] -> [Prop name] -> PropSyn name
forall n.
Located n -> Maybe Fixity -> [TParam n] -> [Prop n] -> PropSyn n
PropSyn (Located name -> Located name
forall t. NoPos t => t -> t
noPos Located name
x) Maybe Fixity
f ([TParam name] -> [TParam name]
forall t. NoPos t => t -> t
noPos [TParam name]
y) ([Prop name] -> [Prop name]
forall t. NoPos t => t -> t
noPos [Prop name]
z)
instance NoPos (Expr name) where
noPos :: Expr name -> Expr name
noPos Expr name
expr =
case Expr name
expr of
EVar name
x -> name -> Expr name
forall n. n -> Expr n
EVar name
x
ELit Literal
x -> Literal -> Expr name
forall n. Literal -> Expr n
ELit Literal
x
EGenerate Expr name
x -> Expr name -> Expr name
forall n. Expr n -> Expr n
EGenerate (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x)
ETuple [Expr name]
x -> [Expr name] -> Expr name
forall n. [Expr n] -> Expr n
ETuple ([Expr name] -> [Expr name]
forall t. NoPos t => t -> t
noPos [Expr name]
x)
ERecord Rec (Expr name)
x -> Rec (Expr name) -> Expr name
forall n. Rec (Expr n) -> Expr n
ERecord (((Range, Expr name) -> (Range, Expr name))
-> Rec (Expr name) -> Rec (Expr name)
forall a b. (a -> b) -> RecordMap Ident a -> RecordMap Ident b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Range, Expr name) -> (Range, Expr name)
forall t. NoPos t => t -> t
noPos Rec (Expr name)
x)
ESel Expr name
x Selector
y -> Expr name -> Selector -> Expr name
forall n. Expr n -> Selector -> Expr n
ESel (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x) Selector
y
EUpd Maybe (Expr name)
x [UpdField name]
y -> Maybe (Expr name) -> [UpdField name] -> Expr name
forall n. Maybe (Expr n) -> [UpdField n] -> Expr n
EUpd (Maybe (Expr name) -> Maybe (Expr name)
forall t. NoPos t => t -> t
noPos Maybe (Expr name)
x) ([UpdField name] -> [UpdField name]
forall t. NoPos t => t -> t
noPos [UpdField name]
y)
EList [Expr name]
x -> [Expr name] -> Expr name
forall n. [Expr n] -> Expr n
EList ([Expr name] -> [Expr name]
forall t. NoPos t => t -> t
noPos [Expr name]
x)
EFromTo Type name
x Maybe (Type name)
y Type name
z Maybe (Type name)
t -> Type name
-> Maybe (Type name) -> Type name -> Maybe (Type name) -> Expr name
forall n.
Type n -> Maybe (Type n) -> Type n -> Maybe (Type n) -> Expr n
EFromTo (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
x) (Maybe (Type name) -> Maybe (Type name)
forall t. NoPos t => t -> t
noPos Maybe (Type name)
y) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
z) (Maybe (Type name) -> Maybe (Type name)
forall t. NoPos t => t -> t
noPos Maybe (Type name)
t)
EFromToBy Bool
isStrict Type name
x Type name
y Type name
z Maybe (Type name)
t
-> Bool
-> Type name
-> Type name
-> Type name
-> Maybe (Type name)
-> Expr name
forall n.
Bool -> Type n -> Type n -> Type n -> Maybe (Type n) -> Expr n
EFromToBy Bool
isStrict (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
x) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
y) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
z) (Maybe (Type name) -> Maybe (Type name)
forall t. NoPos t => t -> t
noPos Maybe (Type name)
t)
EFromToDownBy Bool
isStrict Type name
x Type name
y Type name
z Maybe (Type name)
t
-> Bool
-> Type name
-> Type name
-> Type name
-> Maybe (Type name)
-> Expr name
forall n.
Bool -> Type n -> Type n -> Type n -> Maybe (Type n) -> Expr n
EFromToDownBy Bool
isStrict (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
x) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
y) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
z) (Maybe (Type name) -> Maybe (Type name)
forall t. NoPos t => t -> t
noPos Maybe (Type name)
t)
EFromToLessThan Type name
x Type name
y Maybe (Type name)
t -> Type name -> Type name -> Maybe (Type name) -> Expr name
forall n. Type n -> Type n -> Maybe (Type n) -> Expr n
EFromToLessThan (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
x) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
y) (Maybe (Type name) -> Maybe (Type name)
forall t. NoPos t => t -> t
noPos Maybe (Type name)
t)
EInfFrom Expr name
x Maybe (Expr name)
y -> Expr name -> Maybe (Expr name) -> Expr name
forall n. Expr n -> Maybe (Expr n) -> Expr n
EInfFrom (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x) (Maybe (Expr name) -> Maybe (Expr name)
forall t. NoPos t => t -> t
noPos Maybe (Expr name)
y)
EComp Expr name
x [[Match name]]
y -> Expr name -> [[Match name]] -> Expr name
forall n. Expr n -> [[Match n]] -> Expr n
EComp (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x) ([[Match name]] -> [[Match name]]
forall t. NoPos t => t -> t
noPos [[Match name]]
y)
EApp Expr name
x Expr name
y -> Expr name -> Expr name -> Expr name
forall n. Expr n -> Expr n -> Expr n
EApp (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x) (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
y)
EAppT Expr name
x [TypeInst name]
y -> Expr name -> [TypeInst name] -> Expr name
forall n. Expr n -> [TypeInst n] -> Expr n
EAppT (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x) ([TypeInst name] -> [TypeInst name]
forall t. NoPos t => t -> t
noPos [TypeInst name]
y)
EIf Expr name
x Expr name
y Expr name
z -> Expr name -> Expr name -> Expr name -> Expr name
forall n. Expr n -> Expr n -> Expr n -> Expr n
EIf (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x) (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
y) (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
z)
EWhere Expr name
x [Decl name]
y -> Expr name -> [Decl name] -> Expr name
forall n. Expr n -> [Decl n] -> Expr n
EWhere (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x) ([Decl name] -> [Decl name]
forall t. NoPos t => t -> t
noPos [Decl name]
y)
ETyped Expr name
x Type name
y -> Expr name -> Type name -> Expr name
forall n. Expr n -> Type n -> Expr n
ETyped (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
y)
ETypeVal Type name
x -> Type name -> Expr name
forall n. Type n -> Expr n
ETypeVal (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
x)
EFun FunDesc name
dsc [Pattern name]
x Expr name
y -> FunDesc name -> [Pattern name] -> Expr name -> Expr name
forall n. FunDesc n -> [Pattern n] -> Expr n -> Expr n
EFun FunDesc name
dsc ([Pattern name] -> [Pattern name]
forall t. NoPos t => t -> t
noPos [Pattern name]
x) (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
y)
ELocated Expr name
x Range
_ -> Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x
ESplit Expr name
x -> Expr name -> Expr name
forall n. Expr n -> Expr n
ESplit (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x)
EParens Expr name
e -> Expr name -> Expr name
forall n. Expr n -> Expr n
EParens (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
e)
EInfix Expr name
x Located name
y Fixity
f Expr name
z -> Expr name -> Located name -> Fixity -> Expr name -> Expr name
forall n. Expr n -> Located n -> Fixity -> Expr n -> Expr n
EInfix (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x) Located name
y Fixity
f (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
z)
EPrefix PrefixOp
op Expr name
x -> PrefixOp -> Expr name -> Expr name
forall n. PrefixOp -> Expr n -> Expr n
EPrefix PrefixOp
op (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x)
ECase Expr name
x [CaseAlt name]
y -> Expr name -> [CaseAlt name] -> Expr name
forall n. Expr n -> [CaseAlt n] -> Expr n
ECase (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
x) ([CaseAlt name] -> [CaseAlt name]
forall t. NoPos t => t -> t
noPos [CaseAlt name]
y)
instance NoPos (UpdField name) where
noPos :: UpdField name -> UpdField name
noPos (UpdField UpdHow
h [Located Selector]
xs Expr name
e) = UpdHow -> [Located Selector] -> Expr name -> UpdField name
forall n. UpdHow -> [Located Selector] -> Expr n -> UpdField n
UpdField UpdHow
h [Located Selector]
xs (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
e)
instance NoPos (TypeInst name) where
noPos :: TypeInst name -> TypeInst name
noPos (PosInst Type name
ts) = Type name -> TypeInst name
forall name. Type name -> TypeInst name
PosInst (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
ts)
noPos (NamedInst Named (Type name)
fs) = Named (Type name) -> TypeInst name
forall name. Named (Type name) -> TypeInst name
NamedInst (Named (Type name) -> Named (Type name)
forall t. NoPos t => t -> t
noPos Named (Type name)
fs)
instance NoPos (Match name) where
noPos :: Match name -> Match name
noPos (Match Pattern name
x Expr name
y) = Pattern name -> Expr name -> Match name
forall name. Pattern name -> Expr name -> Match name
Match (Pattern name -> Pattern name
forall t. NoPos t => t -> t
noPos Pattern name
x) (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
y)
noPos (MatchLet Bind name
b) = Bind name -> Match name
forall name. Bind name -> Match name
MatchLet (Bind name -> Bind name
forall t. NoPos t => t -> t
noPos Bind name
b)
instance NoPos (CaseAlt name) where
noPos :: CaseAlt name -> CaseAlt name
noPos (CaseAlt Pattern name
p Expr name
e) = Pattern name -> Expr name -> CaseAlt name
forall n. Pattern n -> Expr n -> CaseAlt n
CaseAlt (Pattern name -> Pattern name
forall t. NoPos t => t -> t
noPos Pattern name
p) (Expr name -> Expr name
forall t. NoPos t => t -> t
noPos Expr name
e)
instance NoPos (Pattern name) where
noPos :: Pattern name -> Pattern name
noPos Pattern name
pat =
case Pattern name
pat of
PVar Located name
x -> Located name -> Pattern name
forall n. Located n -> Pattern n
PVar (Located name -> Located name
forall t. NoPos t => t -> t
noPos Located name
x)
Pattern name
PWild -> Pattern name
forall n. Pattern n
PWild
PTuple [Pattern name]
x -> [Pattern name] -> Pattern name
forall n. [Pattern n] -> Pattern n
PTuple ([Pattern name] -> [Pattern name]
forall t. NoPos t => t -> t
noPos [Pattern name]
x)
PRecord Rec (Pattern name)
x -> Rec (Pattern name) -> Pattern name
forall n. Rec (Pattern n) -> Pattern n
PRecord (((Range, Pattern name) -> (Range, Pattern name))
-> Rec (Pattern name) -> Rec (Pattern name)
forall a b. (a -> b) -> RecordMap Ident a -> RecordMap Ident b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Range, Pattern name) -> (Range, Pattern name)
forall t. NoPos t => t -> t
noPos Rec (Pattern name)
x)
PList [Pattern name]
x -> [Pattern name] -> Pattern name
forall n. [Pattern n] -> Pattern n
PList ([Pattern name] -> [Pattern name]
forall t. NoPos t => t -> t
noPos [Pattern name]
x)
PTyped Pattern name
x Type name
y -> Pattern name -> Type name -> Pattern name
forall n. Pattern n -> Type n -> Pattern n
PTyped (Pattern name -> Pattern name
forall t. NoPos t => t -> t
noPos Pattern name
x) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
y)
PSplit Pattern name
x Pattern name
y -> Pattern name -> Pattern name -> Pattern name
forall n. Pattern n -> Pattern n -> Pattern n
PSplit (Pattern name -> Pattern name
forall t. NoPos t => t -> t
noPos Pattern name
x) (Pattern name -> Pattern name
forall t. NoPos t => t -> t
noPos Pattern name
y)
PLocated Pattern name
x Range
_ -> Pattern name -> Pattern name
forall t. NoPos t => t -> t
noPos Pattern name
x
PCon Located name
n [Pattern name]
ps -> Located name -> [Pattern name] -> Pattern name
forall n. Located n -> [Pattern n] -> Pattern n
PCon Located name
n ([Pattern name] -> [Pattern name]
forall t. NoPos t => t -> t
noPos [Pattern name]
ps)
instance NoPos (Schema name) where
noPos :: Schema name -> Schema name
noPos (Forall [TParam name]
x [Prop name]
y Type name
z Maybe Range
_) = [TParam name]
-> [Prop name] -> Type name -> Maybe Range -> Schema name
forall n.
[TParam n] -> [Prop n] -> Type n -> Maybe Range -> Schema n
Forall ([TParam name] -> [TParam name]
forall t. NoPos t => t -> t
noPos [TParam name]
x) ([Prop name] -> [Prop name]
forall t. NoPos t => t -> t
noPos [Prop name]
y) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
z) Maybe Range
forall a. Maybe a
Nothing
instance NoPos (TParam name) where
noPos :: TParam name -> TParam name
noPos (TParam name
x Maybe Kind
y Maybe Range
_) = name -> Maybe Kind -> Maybe Range -> TParam name
forall n. n -> Maybe Kind -> Maybe Range -> TParam n
TParam name
x Maybe Kind
y Maybe Range
forall a. Maybe a
Nothing
instance NoPos (Type name) where
noPos :: Type name -> Type name
noPos Type name
ty =
case Type name
ty of
Type name
TWild -> Type name
forall n. Type n
TWild
TUser name
x [Type name]
y -> name -> [Type name] -> Type name
forall n. n -> [Type n] -> Type n
TUser name
x ([Type name] -> [Type name]
forall t. NoPos t => t -> t
noPos [Type name]
y)
TTyApp [Named (Type name)]
x -> [Named (Type name)] -> Type name
forall n. [Named (Type n)] -> Type n
TTyApp ([Named (Type name)] -> [Named (Type name)]
forall t. NoPos t => t -> t
noPos [Named (Type name)]
x)
TRecord Rec (Type name)
x -> Rec (Type name) -> Type name
forall n. Rec (Type n) -> Type n
TRecord (((Range, Type name) -> (Range, Type name))
-> Rec (Type name) -> Rec (Type name)
forall a b. (a -> b) -> RecordMap Ident a -> RecordMap Ident b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Range, Type name) -> (Range, Type name)
forall t. NoPos t => t -> t
noPos Rec (Type name)
x)
TTuple [Type name]
x -> [Type name] -> Type name
forall n. [Type n] -> Type n
TTuple ([Type name] -> [Type name]
forall t. NoPos t => t -> t
noPos [Type name]
x)
TFun Type name
x Type name
y -> Type name -> Type name -> Type name
forall n. Type n -> Type n -> Type n
TFun (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
x) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
y)
TSeq Type name
x Type name
y -> Type name -> Type name -> Type name
forall n. Type n -> Type n -> Type n
TSeq (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
x) (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
y)
Type name
TBit -> Type name
forall n. Type n
TBit
TNum Integer
n -> Integer -> Type name
forall n. Integer -> Type n
TNum Integer
n
TChar Char
n -> Char -> Type name
forall n. Char -> Type n
TChar Char
n
TLocated Type name
x Range
_ -> Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
x
TParens Type name
x Maybe Kind
k -> Type name -> Maybe Kind -> Type name
forall n. Type n -> Maybe Kind -> Type n
TParens (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
x) Maybe Kind
k
TInfix Type name
x Located name
y Fixity
f Type name
z-> Type name -> Located name -> Fixity -> Type name -> Type name
forall n. Type n -> Located n -> Fixity -> Type n -> Type n
TInfix (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
x) Located name
y Fixity
f (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
z)
instance NoPos (Prop name) where
noPos :: Prop name -> Prop name
noPos (CType Type name
t) = Type name -> Prop name
forall n. Type n -> Prop n
CType (Type name -> Type name
forall t. NoPos t => t -> t
noPos Type name
t)