{-# LANGUAGE DeriveTraversable #-}
module GF.Grammar.Canonical where
import Prelude hiding ((<>))
import GF.Text.Pretty
import GF.Infra.Ident (RawIdent)
data Grammar = Grammar Abstract [Concrete] deriving Int -> Grammar -> ShowS
[Grammar] -> ShowS
Grammar -> String
(Int -> Grammar -> ShowS)
-> (Grammar -> String) -> ([Grammar] -> ShowS) -> Show Grammar
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Grammar] -> ShowS
$cshowList :: [Grammar] -> ShowS
show :: Grammar -> String
$cshow :: Grammar -> String
showsPrec :: Int -> Grammar -> ShowS
$cshowsPrec :: Int -> Grammar -> ShowS
Show
data Abstract = Abstract ModId Flags [CatDef] [FunDef] deriving Int -> Abstract -> ShowS
[Abstract] -> ShowS
Abstract -> String
(Int -> Abstract -> ShowS)
-> (Abstract -> String) -> ([Abstract] -> ShowS) -> Show Abstract
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Abstract] -> ShowS
$cshowList :: [Abstract] -> ShowS
show :: Abstract -> String
$cshow :: Abstract -> String
showsPrec :: Int -> Abstract -> ShowS
$cshowsPrec :: Int -> Abstract -> ShowS
Show
abstrName :: Abstract -> ModId
abstrName (Abstract ModId
mn Flags
_ [CatDef]
_ [FunDef]
_) = ModId
mn
data CatDef   = CatDef CatId [CatId]        deriving Int -> CatDef -> ShowS
[CatDef] -> ShowS
CatDef -> String
(Int -> CatDef -> ShowS)
-> (CatDef -> String) -> ([CatDef] -> ShowS) -> Show CatDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CatDef] -> ShowS
$cshowList :: [CatDef] -> ShowS
show :: CatDef -> String
$cshow :: CatDef -> String
showsPrec :: Int -> CatDef -> ShowS
$cshowsPrec :: Int -> CatDef -> ShowS
Show
data FunDef   = FunDef FunId Type           deriving Int -> FunDef -> ShowS
[FunDef] -> ShowS
FunDef -> String
(Int -> FunDef -> ShowS)
-> (FunDef -> String) -> ([FunDef] -> ShowS) -> Show FunDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FunDef] -> ShowS
$cshowList :: [FunDef] -> ShowS
show :: FunDef -> String
$cshow :: FunDef -> String
showsPrec :: Int -> FunDef -> ShowS
$cshowsPrec :: Int -> FunDef -> ShowS
Show
data Type     = Type [TypeBinding] TypeApp  deriving Int -> Type -> ShowS
[Type] -> ShowS
Type -> String
(Int -> Type -> ShowS)
-> (Type -> String) -> ([Type] -> ShowS) -> Show Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Type] -> ShowS
$cshowList :: [Type] -> ShowS
show :: Type -> String
$cshow :: Type -> String
showsPrec :: Int -> Type -> ShowS
$cshowsPrec :: Int -> Type -> ShowS
Show
data TypeApp  = TypeApp CatId [Type]        deriving Int -> TypeApp -> ShowS
[TypeApp] -> ShowS
TypeApp -> String
(Int -> TypeApp -> ShowS)
-> (TypeApp -> String) -> ([TypeApp] -> ShowS) -> Show TypeApp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeApp] -> ShowS
$cshowList :: [TypeApp] -> ShowS
show :: TypeApp -> String
$cshow :: TypeApp -> String
showsPrec :: Int -> TypeApp -> ShowS
$cshowsPrec :: Int -> TypeApp -> ShowS
Show
data TypeBinding = TypeBinding VarId Type   deriving Int -> TypeBinding -> ShowS
[TypeBinding] -> ShowS
TypeBinding -> String
(Int -> TypeBinding -> ShowS)
-> (TypeBinding -> String)
-> ([TypeBinding] -> ShowS)
-> Show TypeBinding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeBinding] -> ShowS
$cshowList :: [TypeBinding] -> ShowS
show :: TypeBinding -> String
$cshow :: TypeBinding -> String
showsPrec :: Int -> TypeBinding -> ShowS
$cshowsPrec :: Int -> TypeBinding -> ShowS
Show
data Concrete  = Concrete ModId ModId Flags [ParamDef] [LincatDef] [LinDef]
                 deriving Int -> Concrete -> ShowS
[Concrete] -> ShowS
Concrete -> String
(Int -> Concrete -> ShowS)
-> (Concrete -> String) -> ([Concrete] -> ShowS) -> Show Concrete
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Concrete] -> ShowS
$cshowList :: [Concrete] -> ShowS
show :: Concrete -> String
$cshow :: Concrete -> String
showsPrec :: Int -> Concrete -> ShowS
$cshowsPrec :: Int -> Concrete -> ShowS
Show
concName :: Concrete -> ModId
concName (Concrete ModId
cnc ModId
_ Flags
_ [ParamDef]
_ [LincatDef]
_ [LinDef]
_) = ModId
cnc
data ParamDef  = ParamDef ParamId [ParamValueDef]
               | ParamAliasDef ParamId LinType
               deriving Int -> ParamDef -> ShowS
[ParamDef] -> ShowS
ParamDef -> String
(Int -> ParamDef -> ShowS)
-> (ParamDef -> String) -> ([ParamDef] -> ShowS) -> Show ParamDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParamDef] -> ShowS
$cshowList :: [ParamDef] -> ShowS
show :: ParamDef -> String
$cshow :: ParamDef -> String
showsPrec :: Int -> ParamDef -> ShowS
$cshowsPrec :: Int -> ParamDef -> ShowS
Show
data LincatDef = LincatDef CatId LinType  deriving Int -> LincatDef -> ShowS
[LincatDef] -> ShowS
LincatDef -> String
(Int -> LincatDef -> ShowS)
-> (LincatDef -> String)
-> ([LincatDef] -> ShowS)
-> Show LincatDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LincatDef] -> ShowS
$cshowList :: [LincatDef] -> ShowS
show :: LincatDef -> String
$cshow :: LincatDef -> String
showsPrec :: Int -> LincatDef -> ShowS
$cshowsPrec :: Int -> LincatDef -> ShowS
Show
data LinDef    = LinDef FunId [VarId] LinValue  deriving Int -> LinDef -> ShowS
[LinDef] -> ShowS
LinDef -> String
(Int -> LinDef -> ShowS)
-> (LinDef -> String) -> ([LinDef] -> ShowS) -> Show LinDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LinDef] -> ShowS
$cshowList :: [LinDef] -> ShowS
show :: LinDef -> String
$cshow :: LinDef -> String
showsPrec :: Int -> LinDef -> ShowS
$cshowsPrec :: Int -> LinDef -> ShowS
Show
data LinType = FloatType
             | IntType
             | ParamType ParamType
             | RecordType [RecordRowType]
             | StrType
             | TableType LinType LinType
             | TupleType [LinType]
              deriving (LinType -> LinType -> Bool
(LinType -> LinType -> Bool)
-> (LinType -> LinType -> Bool) -> Eq LinType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LinType -> LinType -> Bool
$c/= :: LinType -> LinType -> Bool
== :: LinType -> LinType -> Bool
$c== :: LinType -> LinType -> Bool
Eq,Eq LinType
Eq LinType
-> (LinType -> LinType -> Ordering)
-> (LinType -> LinType -> Bool)
-> (LinType -> LinType -> Bool)
-> (LinType -> LinType -> Bool)
-> (LinType -> LinType -> Bool)
-> (LinType -> LinType -> LinType)
-> (LinType -> LinType -> LinType)
-> Ord LinType
LinType -> LinType -> Bool
LinType -> LinType -> Ordering
LinType -> LinType -> LinType
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
min :: LinType -> LinType -> LinType
$cmin :: LinType -> LinType -> LinType
max :: LinType -> LinType -> LinType
$cmax :: LinType -> LinType -> LinType
>= :: LinType -> LinType -> Bool
$c>= :: LinType -> LinType -> Bool
> :: LinType -> LinType -> Bool
$c> :: LinType -> LinType -> Bool
<= :: LinType -> LinType -> Bool
$c<= :: LinType -> LinType -> Bool
< :: LinType -> LinType -> Bool
$c< :: LinType -> LinType -> Bool
compare :: LinType -> LinType -> Ordering
$ccompare :: LinType -> LinType -> Ordering
$cp1Ord :: Eq LinType
Ord,Int -> LinType -> ShowS
[LinType] -> ShowS
LinType -> String
(Int -> LinType -> ShowS)
-> (LinType -> String) -> ([LinType] -> ShowS) -> Show LinType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LinType] -> ShowS
$cshowList :: [LinType] -> ShowS
show :: LinType -> String
$cshow :: LinType -> String
showsPrec :: Int -> LinType -> ShowS
$cshowsPrec :: Int -> LinType -> ShowS
Show)
newtype ParamType = ParamTypeId ParamId deriving (ParamType -> ParamType -> Bool
(ParamType -> ParamType -> Bool)
-> (ParamType -> ParamType -> Bool) -> Eq ParamType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParamType -> ParamType -> Bool
$c/= :: ParamType -> ParamType -> Bool
== :: ParamType -> ParamType -> Bool
$c== :: ParamType -> ParamType -> Bool
Eq,Eq ParamType
Eq ParamType
-> (ParamType -> ParamType -> Ordering)
-> (ParamType -> ParamType -> Bool)
-> (ParamType -> ParamType -> Bool)
-> (ParamType -> ParamType -> Bool)
-> (ParamType -> ParamType -> Bool)
-> (ParamType -> ParamType -> ParamType)
-> (ParamType -> ParamType -> ParamType)
-> Ord ParamType
ParamType -> ParamType -> Bool
ParamType -> ParamType -> Ordering
ParamType -> ParamType -> ParamType
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
min :: ParamType -> ParamType -> ParamType
$cmin :: ParamType -> ParamType -> ParamType
max :: ParamType -> ParamType -> ParamType
$cmax :: ParamType -> ParamType -> ParamType
>= :: ParamType -> ParamType -> Bool
$c>= :: ParamType -> ParamType -> Bool
> :: ParamType -> ParamType -> Bool
$c> :: ParamType -> ParamType -> Bool
<= :: ParamType -> ParamType -> Bool
$c<= :: ParamType -> ParamType -> Bool
< :: ParamType -> ParamType -> Bool
$c< :: ParamType -> ParamType -> Bool
compare :: ParamType -> ParamType -> Ordering
$ccompare :: ParamType -> ParamType -> Ordering
$cp1Ord :: Eq ParamType
Ord,Int -> ParamType -> ShowS
[ParamType] -> ShowS
ParamType -> String
(Int -> ParamType -> ShowS)
-> (ParamType -> String)
-> ([ParamType] -> ShowS)
-> Show ParamType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParamType] -> ShowS
$cshowList :: [ParamType] -> ShowS
show :: ParamType -> String
$cshow :: ParamType -> String
showsPrec :: Int -> ParamType -> ShowS
$cshowsPrec :: Int -> ParamType -> ShowS
Show)
data LinValue = ConcatValue LinValue LinValue
              | LiteralValue LinLiteral
              | ErrorValue String
              | ParamConstant ParamValue
              | PredefValue PredefId
              | RecordValue [RecordRowValue]
              | TableValue LinType [TableRowValue]
              | TupleValue [LinValue]
              | VariantValue [LinValue]
              | VarValue VarValueId
              | PreValue [([String], LinValue)] LinValue
              | Projection LinValue LabelId
              | Selection LinValue LinValue
              |  String LinValue
              deriving (LinValue -> LinValue -> Bool
(LinValue -> LinValue -> Bool)
-> (LinValue -> LinValue -> Bool) -> Eq LinValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LinValue -> LinValue -> Bool
$c/= :: LinValue -> LinValue -> Bool
== :: LinValue -> LinValue -> Bool
$c== :: LinValue -> LinValue -> Bool
Eq,Eq LinValue
Eq LinValue
-> (LinValue -> LinValue -> Ordering)
-> (LinValue -> LinValue -> Bool)
-> (LinValue -> LinValue -> Bool)
-> (LinValue -> LinValue -> Bool)
-> (LinValue -> LinValue -> Bool)
-> (LinValue -> LinValue -> LinValue)
-> (LinValue -> LinValue -> LinValue)
-> Ord LinValue
LinValue -> LinValue -> Bool
LinValue -> LinValue -> Ordering
LinValue -> LinValue -> LinValue
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
min :: LinValue -> LinValue -> LinValue
$cmin :: LinValue -> LinValue -> LinValue
max :: LinValue -> LinValue -> LinValue
$cmax :: LinValue -> LinValue -> LinValue
>= :: LinValue -> LinValue -> Bool
$c>= :: LinValue -> LinValue -> Bool
> :: LinValue -> LinValue -> Bool
$c> :: LinValue -> LinValue -> Bool
<= :: LinValue -> LinValue -> Bool
$c<= :: LinValue -> LinValue -> Bool
< :: LinValue -> LinValue -> Bool
$c< :: LinValue -> LinValue -> Bool
compare :: LinValue -> LinValue -> Ordering
$ccompare :: LinValue -> LinValue -> Ordering
$cp1Ord :: Eq LinValue
Ord,Int -> LinValue -> ShowS
[LinValue] -> ShowS
LinValue -> String
(Int -> LinValue -> ShowS)
-> (LinValue -> String) -> ([LinValue] -> ShowS) -> Show LinValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LinValue] -> ShowS
$cshowList :: [LinValue] -> ShowS
show :: LinValue -> String
$cshow :: LinValue -> String
showsPrec :: Int -> LinValue -> ShowS
$cshowsPrec :: Int -> LinValue -> ShowS
Show)
data LinLiteral = FloatConstant Float
                | IntConstant Int
                | StrConstant String
                deriving (LinLiteral -> LinLiteral -> Bool
(LinLiteral -> LinLiteral -> Bool)
-> (LinLiteral -> LinLiteral -> Bool) -> Eq LinLiteral
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LinLiteral -> LinLiteral -> Bool
$c/= :: LinLiteral -> LinLiteral -> Bool
== :: LinLiteral -> LinLiteral -> Bool
$c== :: LinLiteral -> LinLiteral -> Bool
Eq,Eq LinLiteral
Eq LinLiteral
-> (LinLiteral -> LinLiteral -> Ordering)
-> (LinLiteral -> LinLiteral -> Bool)
-> (LinLiteral -> LinLiteral -> Bool)
-> (LinLiteral -> LinLiteral -> Bool)
-> (LinLiteral -> LinLiteral -> Bool)
-> (LinLiteral -> LinLiteral -> LinLiteral)
-> (LinLiteral -> LinLiteral -> LinLiteral)
-> Ord LinLiteral
LinLiteral -> LinLiteral -> Bool
LinLiteral -> LinLiteral -> Ordering
LinLiteral -> LinLiteral -> LinLiteral
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
min :: LinLiteral -> LinLiteral -> LinLiteral
$cmin :: LinLiteral -> LinLiteral -> LinLiteral
max :: LinLiteral -> LinLiteral -> LinLiteral
$cmax :: LinLiteral -> LinLiteral -> LinLiteral
>= :: LinLiteral -> LinLiteral -> Bool
$c>= :: LinLiteral -> LinLiteral -> Bool
> :: LinLiteral -> LinLiteral -> Bool
$c> :: LinLiteral -> LinLiteral -> Bool
<= :: LinLiteral -> LinLiteral -> Bool
$c<= :: LinLiteral -> LinLiteral -> Bool
< :: LinLiteral -> LinLiteral -> Bool
$c< :: LinLiteral -> LinLiteral -> Bool
compare :: LinLiteral -> LinLiteral -> Ordering
$ccompare :: LinLiteral -> LinLiteral -> Ordering
$cp1Ord :: Eq LinLiteral
Ord,Int -> LinLiteral -> ShowS
[LinLiteral] -> ShowS
LinLiteral -> String
(Int -> LinLiteral -> ShowS)
-> (LinLiteral -> String)
-> ([LinLiteral] -> ShowS)
-> Show LinLiteral
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LinLiteral] -> ShowS
$cshowList :: [LinLiteral] -> ShowS
show :: LinLiteral -> String
$cshow :: LinLiteral -> String
showsPrec :: Int -> LinLiteral -> ShowS
$cshowsPrec :: Int -> LinLiteral -> ShowS
Show)
data LinPattern = ParamPattern ParamPattern
                | RecordPattern [RecordRow LinPattern]
                | TuplePattern [LinPattern]
                | WildPattern
                deriving (LinPattern -> LinPattern -> Bool
(LinPattern -> LinPattern -> Bool)
-> (LinPattern -> LinPattern -> Bool) -> Eq LinPattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LinPattern -> LinPattern -> Bool
$c/= :: LinPattern -> LinPattern -> Bool
== :: LinPattern -> LinPattern -> Bool
$c== :: LinPattern -> LinPattern -> Bool
Eq,Eq LinPattern
Eq LinPattern
-> (LinPattern -> LinPattern -> Ordering)
-> (LinPattern -> LinPattern -> Bool)
-> (LinPattern -> LinPattern -> Bool)
-> (LinPattern -> LinPattern -> Bool)
-> (LinPattern -> LinPattern -> Bool)
-> (LinPattern -> LinPattern -> LinPattern)
-> (LinPattern -> LinPattern -> LinPattern)
-> Ord LinPattern
LinPattern -> LinPattern -> Bool
LinPattern -> LinPattern -> Ordering
LinPattern -> LinPattern -> LinPattern
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
min :: LinPattern -> LinPattern -> LinPattern
$cmin :: LinPattern -> LinPattern -> LinPattern
max :: LinPattern -> LinPattern -> LinPattern
$cmax :: LinPattern -> LinPattern -> LinPattern
>= :: LinPattern -> LinPattern -> Bool
$c>= :: LinPattern -> LinPattern -> Bool
> :: LinPattern -> LinPattern -> Bool
$c> :: LinPattern -> LinPattern -> Bool
<= :: LinPattern -> LinPattern -> Bool
$c<= :: LinPattern -> LinPattern -> Bool
< :: LinPattern -> LinPattern -> Bool
$c< :: LinPattern -> LinPattern -> Bool
compare :: LinPattern -> LinPattern -> Ordering
$ccompare :: LinPattern -> LinPattern -> Ordering
$cp1Ord :: Eq LinPattern
Ord,Int -> LinPattern -> ShowS
[LinPattern] -> ShowS
LinPattern -> String
(Int -> LinPattern -> ShowS)
-> (LinPattern -> String)
-> ([LinPattern] -> ShowS)
-> Show LinPattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LinPattern] -> ShowS
$cshowList :: [LinPattern] -> ShowS
show :: LinPattern -> String
$cshow :: LinPattern -> String
showsPrec :: Int -> LinPattern -> ShowS
$cshowsPrec :: Int -> LinPattern -> ShowS
Show)
type ParamValue = Param LinValue
type ParamPattern = Param LinPattern
type ParamValueDef = Param ParamId
data Param arg = Param ParamId [arg]
                 deriving (Param arg -> Param arg -> Bool
(Param arg -> Param arg -> Bool)
-> (Param arg -> Param arg -> Bool) -> Eq (Param arg)
forall arg. Eq arg => Param arg -> Param arg -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Param arg -> Param arg -> Bool
$c/= :: forall arg. Eq arg => Param arg -> Param arg -> Bool
== :: Param arg -> Param arg -> Bool
$c== :: forall arg. Eq arg => Param arg -> Param arg -> Bool
Eq,Eq (Param arg)
Eq (Param arg)
-> (Param arg -> Param arg -> Ordering)
-> (Param arg -> Param arg -> Bool)
-> (Param arg -> Param arg -> Bool)
-> (Param arg -> Param arg -> Bool)
-> (Param arg -> Param arg -> Bool)
-> (Param arg -> Param arg -> Param arg)
-> (Param arg -> Param arg -> Param arg)
-> Ord (Param arg)
Param arg -> Param arg -> Bool
Param arg -> Param arg -> Ordering
Param arg -> Param arg -> Param arg
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 arg. Ord arg => Eq (Param arg)
forall arg. Ord arg => Param arg -> Param arg -> Bool
forall arg. Ord arg => Param arg -> Param arg -> Ordering
forall arg. Ord arg => Param arg -> Param arg -> Param arg
min :: Param arg -> Param arg -> Param arg
$cmin :: forall arg. Ord arg => Param arg -> Param arg -> Param arg
max :: Param arg -> Param arg -> Param arg
$cmax :: forall arg. Ord arg => Param arg -> Param arg -> Param arg
>= :: Param arg -> Param arg -> Bool
$c>= :: forall arg. Ord arg => Param arg -> Param arg -> Bool
> :: Param arg -> Param arg -> Bool
$c> :: forall arg. Ord arg => Param arg -> Param arg -> Bool
<= :: Param arg -> Param arg -> Bool
$c<= :: forall arg. Ord arg => Param arg -> Param arg -> Bool
< :: Param arg -> Param arg -> Bool
$c< :: forall arg. Ord arg => Param arg -> Param arg -> Bool
compare :: Param arg -> Param arg -> Ordering
$ccompare :: forall arg. Ord arg => Param arg -> Param arg -> Ordering
$cp1Ord :: forall arg. Ord arg => Eq (Param arg)
Ord,Int -> Param arg -> ShowS
[Param arg] -> ShowS
Param arg -> String
(Int -> Param arg -> ShowS)
-> (Param arg -> String)
-> ([Param arg] -> ShowS)
-> Show (Param arg)
forall arg. Show arg => Int -> Param arg -> ShowS
forall arg. Show arg => [Param arg] -> ShowS
forall arg. Show arg => Param arg -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Param arg] -> ShowS
$cshowList :: forall arg. Show arg => [Param arg] -> ShowS
show :: Param arg -> String
$cshow :: forall arg. Show arg => Param arg -> String
showsPrec :: Int -> Param arg -> ShowS
$cshowsPrec :: forall arg. Show arg => Int -> Param arg -> ShowS
Show,a -> Param b -> Param a
(a -> b) -> Param a -> Param b
(forall a b. (a -> b) -> Param a -> Param b)
-> (forall a b. a -> Param b -> Param a) -> Functor Param
forall a b. a -> Param b -> Param a
forall a b. (a -> b) -> Param a -> Param b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Param b -> Param a
$c<$ :: forall a b. a -> Param b -> Param a
fmap :: (a -> b) -> Param a -> Param b
$cfmap :: forall a b. (a -> b) -> Param a -> Param b
Functor,Param a -> Bool
(a -> m) -> Param a -> m
(a -> b -> b) -> b -> Param a -> b
(forall m. Monoid m => Param m -> m)
-> (forall m a. Monoid m => (a -> m) -> Param a -> m)
-> (forall m a. Monoid m => (a -> m) -> Param a -> m)
-> (forall a b. (a -> b -> b) -> b -> Param a -> b)
-> (forall a b. (a -> b -> b) -> b -> Param a -> b)
-> (forall b a. (b -> a -> b) -> b -> Param a -> b)
-> (forall b a. (b -> a -> b) -> b -> Param a -> b)
-> (forall a. (a -> a -> a) -> Param a -> a)
-> (forall a. (a -> a -> a) -> Param a -> a)
-> (forall a. Param a -> [a])
-> (forall a. Param a -> Bool)
-> (forall a. Param a -> Int)
-> (forall a. Eq a => a -> Param a -> Bool)
-> (forall a. Ord a => Param a -> a)
-> (forall a. Ord a => Param a -> a)
-> (forall a. Num a => Param a -> a)
-> (forall a. Num a => Param a -> a)
-> Foldable Param
forall a. Eq a => a -> Param a -> Bool
forall a. Num a => Param a -> a
forall a. Ord a => Param a -> a
forall m. Monoid m => Param m -> m
forall a. Param a -> Bool
forall a. Param a -> Int
forall a. Param a -> [a]
forall a. (a -> a -> a) -> Param a -> a
forall m a. Monoid m => (a -> m) -> Param a -> m
forall b a. (b -> a -> b) -> b -> Param a -> b
forall a b. (a -> b -> b) -> b -> Param 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
product :: Param a -> a
$cproduct :: forall a. Num a => Param a -> a
sum :: Param a -> a
$csum :: forall a. Num a => Param a -> a
minimum :: Param a -> a
$cminimum :: forall a. Ord a => Param a -> a
maximum :: Param a -> a
$cmaximum :: forall a. Ord a => Param a -> a
elem :: a -> Param a -> Bool
$celem :: forall a. Eq a => a -> Param a -> Bool
length :: Param a -> Int
$clength :: forall a. Param a -> Int
null :: Param a -> Bool
$cnull :: forall a. Param a -> Bool
toList :: Param a -> [a]
$ctoList :: forall a. Param a -> [a]
foldl1 :: (a -> a -> a) -> Param a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Param a -> a
foldr1 :: (a -> a -> a) -> Param a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Param a -> a
foldl' :: (b -> a -> b) -> b -> Param a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Param a -> b
foldl :: (b -> a -> b) -> b -> Param a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Param a -> b
foldr' :: (a -> b -> b) -> b -> Param a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Param a -> b
foldr :: (a -> b -> b) -> b -> Param a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Param a -> b
foldMap' :: (a -> m) -> Param a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Param a -> m
foldMap :: (a -> m) -> Param a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Param a -> m
fold :: Param m -> m
$cfold :: forall m. Monoid m => Param m -> m
Foldable,Functor Param
Foldable Param
Functor Param
-> Foldable Param
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Param a -> f (Param b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Param (f a) -> f (Param a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Param a -> m (Param b))
-> (forall (m :: * -> *) a. Monad m => Param (m a) -> m (Param a))
-> Traversable Param
(a -> f b) -> Param a -> f (Param b)
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 => Param (m a) -> m (Param a)
forall (f :: * -> *) a. Applicative f => Param (f a) -> f (Param a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Param a -> m (Param b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Param a -> f (Param b)
sequence :: Param (m a) -> m (Param a)
$csequence :: forall (m :: * -> *) a. Monad m => Param (m a) -> m (Param a)
mapM :: (a -> m b) -> Param a -> m (Param b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Param a -> m (Param b)
sequenceA :: Param (f a) -> f (Param a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Param (f a) -> f (Param a)
traverse :: (a -> f b) -> Param a -> f (Param b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Param a -> f (Param b)
$cp2Traversable :: Foldable Param
$cp1Traversable :: Functor Param
Traversable)
type RecordRowType  = RecordRow LinType
type RecordRowValue = RecordRow LinValue
type TableRowValue  = TableRow LinValue
data RecordRow rhs = RecordRow LabelId    rhs
                     deriving (RecordRow rhs -> RecordRow rhs -> Bool
(RecordRow rhs -> RecordRow rhs -> Bool)
-> (RecordRow rhs -> RecordRow rhs -> Bool) -> Eq (RecordRow rhs)
forall rhs. Eq rhs => RecordRow rhs -> RecordRow rhs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecordRow rhs -> RecordRow rhs -> Bool
$c/= :: forall rhs. Eq rhs => RecordRow rhs -> RecordRow rhs -> Bool
== :: RecordRow rhs -> RecordRow rhs -> Bool
$c== :: forall rhs. Eq rhs => RecordRow rhs -> RecordRow rhs -> Bool
Eq,Eq (RecordRow rhs)
Eq (RecordRow rhs)
-> (RecordRow rhs -> RecordRow rhs -> Ordering)
-> (RecordRow rhs -> RecordRow rhs -> Bool)
-> (RecordRow rhs -> RecordRow rhs -> Bool)
-> (RecordRow rhs -> RecordRow rhs -> Bool)
-> (RecordRow rhs -> RecordRow rhs -> Bool)
-> (RecordRow rhs -> RecordRow rhs -> RecordRow rhs)
-> (RecordRow rhs -> RecordRow rhs -> RecordRow rhs)
-> Ord (RecordRow rhs)
RecordRow rhs -> RecordRow rhs -> Bool
RecordRow rhs -> RecordRow rhs -> Ordering
RecordRow rhs -> RecordRow rhs -> RecordRow rhs
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 rhs. Ord rhs => Eq (RecordRow rhs)
forall rhs. Ord rhs => RecordRow rhs -> RecordRow rhs -> Bool
forall rhs. Ord rhs => RecordRow rhs -> RecordRow rhs -> Ordering
forall rhs.
Ord rhs =>
RecordRow rhs -> RecordRow rhs -> RecordRow rhs
min :: RecordRow rhs -> RecordRow rhs -> RecordRow rhs
$cmin :: forall rhs.
Ord rhs =>
RecordRow rhs -> RecordRow rhs -> RecordRow rhs
max :: RecordRow rhs -> RecordRow rhs -> RecordRow rhs
$cmax :: forall rhs.
Ord rhs =>
RecordRow rhs -> RecordRow rhs -> RecordRow rhs
>= :: RecordRow rhs -> RecordRow rhs -> Bool
$c>= :: forall rhs. Ord rhs => RecordRow rhs -> RecordRow rhs -> Bool
> :: RecordRow rhs -> RecordRow rhs -> Bool
$c> :: forall rhs. Ord rhs => RecordRow rhs -> RecordRow rhs -> Bool
<= :: RecordRow rhs -> RecordRow rhs -> Bool
$c<= :: forall rhs. Ord rhs => RecordRow rhs -> RecordRow rhs -> Bool
< :: RecordRow rhs -> RecordRow rhs -> Bool
$c< :: forall rhs. Ord rhs => RecordRow rhs -> RecordRow rhs -> Bool
compare :: RecordRow rhs -> RecordRow rhs -> Ordering
$ccompare :: forall rhs. Ord rhs => RecordRow rhs -> RecordRow rhs -> Ordering
$cp1Ord :: forall rhs. Ord rhs => Eq (RecordRow rhs)
Ord,Int -> RecordRow rhs -> ShowS
[RecordRow rhs] -> ShowS
RecordRow rhs -> String
(Int -> RecordRow rhs -> ShowS)
-> (RecordRow rhs -> String)
-> ([RecordRow rhs] -> ShowS)
-> Show (RecordRow rhs)
forall rhs. Show rhs => Int -> RecordRow rhs -> ShowS
forall rhs. Show rhs => [RecordRow rhs] -> ShowS
forall rhs. Show rhs => RecordRow rhs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecordRow rhs] -> ShowS
$cshowList :: forall rhs. Show rhs => [RecordRow rhs] -> ShowS
show :: RecordRow rhs -> String
$cshow :: forall rhs. Show rhs => RecordRow rhs -> String
showsPrec :: Int -> RecordRow rhs -> ShowS
$cshowsPrec :: forall rhs. Show rhs => Int -> RecordRow rhs -> ShowS
Show,a -> RecordRow b -> RecordRow a
(a -> b) -> RecordRow a -> RecordRow b
(forall a b. (a -> b) -> RecordRow a -> RecordRow b)
-> (forall a b. a -> RecordRow b -> RecordRow a)
-> Functor RecordRow
forall a b. a -> RecordRow b -> RecordRow a
forall a b. (a -> b) -> RecordRow a -> RecordRow b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> RecordRow b -> RecordRow a
$c<$ :: forall a b. a -> RecordRow b -> RecordRow a
fmap :: (a -> b) -> RecordRow a -> RecordRow b
$cfmap :: forall a b. (a -> b) -> RecordRow a -> RecordRow b
Functor,RecordRow a -> Bool
(a -> m) -> RecordRow a -> m
(a -> b -> b) -> b -> RecordRow a -> b
(forall m. Monoid m => RecordRow m -> m)
-> (forall m a. Monoid m => (a -> m) -> RecordRow a -> m)
-> (forall m a. Monoid m => (a -> m) -> RecordRow a -> m)
-> (forall a b. (a -> b -> b) -> b -> RecordRow a -> b)
-> (forall a b. (a -> b -> b) -> b -> RecordRow a -> b)
-> (forall b a. (b -> a -> b) -> b -> RecordRow a -> b)
-> (forall b a. (b -> a -> b) -> b -> RecordRow a -> b)
-> (forall a. (a -> a -> a) -> RecordRow a -> a)
-> (forall a. (a -> a -> a) -> RecordRow a -> a)
-> (forall a. RecordRow a -> [a])
-> (forall a. RecordRow a -> Bool)
-> (forall a. RecordRow a -> Int)
-> (forall a. Eq a => a -> RecordRow a -> Bool)
-> (forall a. Ord a => RecordRow a -> a)
-> (forall a. Ord a => RecordRow a -> a)
-> (forall a. Num a => RecordRow a -> a)
-> (forall a. Num a => RecordRow a -> a)
-> Foldable RecordRow
forall a. Eq a => a -> RecordRow a -> Bool
forall a. Num a => RecordRow a -> a
forall a. Ord a => RecordRow a -> a
forall m. Monoid m => RecordRow m -> m
forall a. RecordRow a -> Bool
forall a. RecordRow a -> Int
forall a. RecordRow a -> [a]
forall a. (a -> a -> a) -> RecordRow a -> a
forall m a. Monoid m => (a -> m) -> RecordRow a -> m
forall b a. (b -> a -> b) -> b -> RecordRow a -> b
forall a b. (a -> b -> b) -> b -> RecordRow 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
product :: RecordRow a -> a
$cproduct :: forall a. Num a => RecordRow a -> a
sum :: RecordRow a -> a
$csum :: forall a. Num a => RecordRow a -> a
minimum :: RecordRow a -> a
$cminimum :: forall a. Ord a => RecordRow a -> a
maximum :: RecordRow a -> a
$cmaximum :: forall a. Ord a => RecordRow a -> a
elem :: a -> RecordRow a -> Bool
$celem :: forall a. Eq a => a -> RecordRow a -> Bool
length :: RecordRow a -> Int
$clength :: forall a. RecordRow a -> Int
null :: RecordRow a -> Bool
$cnull :: forall a. RecordRow a -> Bool
toList :: RecordRow a -> [a]
$ctoList :: forall a. RecordRow a -> [a]
foldl1 :: (a -> a -> a) -> RecordRow a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> RecordRow a -> a
foldr1 :: (a -> a -> a) -> RecordRow a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> RecordRow a -> a
foldl' :: (b -> a -> b) -> b -> RecordRow a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> RecordRow a -> b
foldl :: (b -> a -> b) -> b -> RecordRow a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> RecordRow a -> b
foldr' :: (a -> b -> b) -> b -> RecordRow a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> RecordRow a -> b
foldr :: (a -> b -> b) -> b -> RecordRow a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> RecordRow a -> b
foldMap' :: (a -> m) -> RecordRow a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> RecordRow a -> m
foldMap :: (a -> m) -> RecordRow a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> RecordRow a -> m
fold :: RecordRow m -> m
$cfold :: forall m. Monoid m => RecordRow m -> m
Foldable,Functor RecordRow
Foldable RecordRow
Functor RecordRow
-> Foldable RecordRow
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> RecordRow a -> f (RecordRow b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    RecordRow (f a) -> f (RecordRow a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> RecordRow a -> m (RecordRow b))
-> (forall (m :: * -> *) a.
    Monad m =>
    RecordRow (m a) -> m (RecordRow a))
-> Traversable RecordRow
(a -> f b) -> RecordRow a -> f (RecordRow b)
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 =>
RecordRow (m a) -> m (RecordRow a)
forall (f :: * -> *) a.
Applicative f =>
RecordRow (f a) -> f (RecordRow a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> RecordRow a -> m (RecordRow b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> RecordRow a -> f (RecordRow b)
sequence :: RecordRow (m a) -> m (RecordRow a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
RecordRow (m a) -> m (RecordRow a)
mapM :: (a -> m b) -> RecordRow a -> m (RecordRow b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> RecordRow a -> m (RecordRow b)
sequenceA :: RecordRow (f a) -> f (RecordRow a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
RecordRow (f a) -> f (RecordRow a)
traverse :: (a -> f b) -> RecordRow a -> f (RecordRow b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> RecordRow a -> f (RecordRow b)
$cp2Traversable :: Foldable RecordRow
$cp1Traversable :: Functor RecordRow
Traversable)
data TableRow  rhs = TableRow  LinPattern rhs
                     deriving (TableRow rhs -> TableRow rhs -> Bool
(TableRow rhs -> TableRow rhs -> Bool)
-> (TableRow rhs -> TableRow rhs -> Bool) -> Eq (TableRow rhs)
forall rhs. Eq rhs => TableRow rhs -> TableRow rhs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableRow rhs -> TableRow rhs -> Bool
$c/= :: forall rhs. Eq rhs => TableRow rhs -> TableRow rhs -> Bool
== :: TableRow rhs -> TableRow rhs -> Bool
$c== :: forall rhs. Eq rhs => TableRow rhs -> TableRow rhs -> Bool
Eq,Eq (TableRow rhs)
Eq (TableRow rhs)
-> (TableRow rhs -> TableRow rhs -> Ordering)
-> (TableRow rhs -> TableRow rhs -> Bool)
-> (TableRow rhs -> TableRow rhs -> Bool)
-> (TableRow rhs -> TableRow rhs -> Bool)
-> (TableRow rhs -> TableRow rhs -> Bool)
-> (TableRow rhs -> TableRow rhs -> TableRow rhs)
-> (TableRow rhs -> TableRow rhs -> TableRow rhs)
-> Ord (TableRow rhs)
TableRow rhs -> TableRow rhs -> Bool
TableRow rhs -> TableRow rhs -> Ordering
TableRow rhs -> TableRow rhs -> TableRow rhs
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 rhs. Ord rhs => Eq (TableRow rhs)
forall rhs. Ord rhs => TableRow rhs -> TableRow rhs -> Bool
forall rhs. Ord rhs => TableRow rhs -> TableRow rhs -> Ordering
forall rhs. Ord rhs => TableRow rhs -> TableRow rhs -> TableRow rhs
min :: TableRow rhs -> TableRow rhs -> TableRow rhs
$cmin :: forall rhs. Ord rhs => TableRow rhs -> TableRow rhs -> TableRow rhs
max :: TableRow rhs -> TableRow rhs -> TableRow rhs
$cmax :: forall rhs. Ord rhs => TableRow rhs -> TableRow rhs -> TableRow rhs
>= :: TableRow rhs -> TableRow rhs -> Bool
$c>= :: forall rhs. Ord rhs => TableRow rhs -> TableRow rhs -> Bool
> :: TableRow rhs -> TableRow rhs -> Bool
$c> :: forall rhs. Ord rhs => TableRow rhs -> TableRow rhs -> Bool
<= :: TableRow rhs -> TableRow rhs -> Bool
$c<= :: forall rhs. Ord rhs => TableRow rhs -> TableRow rhs -> Bool
< :: TableRow rhs -> TableRow rhs -> Bool
$c< :: forall rhs. Ord rhs => TableRow rhs -> TableRow rhs -> Bool
compare :: TableRow rhs -> TableRow rhs -> Ordering
$ccompare :: forall rhs. Ord rhs => TableRow rhs -> TableRow rhs -> Ordering
$cp1Ord :: forall rhs. Ord rhs => Eq (TableRow rhs)
Ord,Int -> TableRow rhs -> ShowS
[TableRow rhs] -> ShowS
TableRow rhs -> String
(Int -> TableRow rhs -> ShowS)
-> (TableRow rhs -> String)
-> ([TableRow rhs] -> ShowS)
-> Show (TableRow rhs)
forall rhs. Show rhs => Int -> TableRow rhs -> ShowS
forall rhs. Show rhs => [TableRow rhs] -> ShowS
forall rhs. Show rhs => TableRow rhs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableRow rhs] -> ShowS
$cshowList :: forall rhs. Show rhs => [TableRow rhs] -> ShowS
show :: TableRow rhs -> String
$cshow :: forall rhs. Show rhs => TableRow rhs -> String
showsPrec :: Int -> TableRow rhs -> ShowS
$cshowsPrec :: forall rhs. Show rhs => Int -> TableRow rhs -> ShowS
Show,a -> TableRow b -> TableRow a
(a -> b) -> TableRow a -> TableRow b
(forall a b. (a -> b) -> TableRow a -> TableRow b)
-> (forall a b. a -> TableRow b -> TableRow a) -> Functor TableRow
forall a b. a -> TableRow b -> TableRow a
forall a b. (a -> b) -> TableRow a -> TableRow b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> TableRow b -> TableRow a
$c<$ :: forall a b. a -> TableRow b -> TableRow a
fmap :: (a -> b) -> TableRow a -> TableRow b
$cfmap :: forall a b. (a -> b) -> TableRow a -> TableRow b
Functor,TableRow a -> Bool
(a -> m) -> TableRow a -> m
(a -> b -> b) -> b -> TableRow a -> b
(forall m. Monoid m => TableRow m -> m)
-> (forall m a. Monoid m => (a -> m) -> TableRow a -> m)
-> (forall m a. Monoid m => (a -> m) -> TableRow a -> m)
-> (forall a b. (a -> b -> b) -> b -> TableRow a -> b)
-> (forall a b. (a -> b -> b) -> b -> TableRow a -> b)
-> (forall b a. (b -> a -> b) -> b -> TableRow a -> b)
-> (forall b a. (b -> a -> b) -> b -> TableRow a -> b)
-> (forall a. (a -> a -> a) -> TableRow a -> a)
-> (forall a. (a -> a -> a) -> TableRow a -> a)
-> (forall a. TableRow a -> [a])
-> (forall a. TableRow a -> Bool)
-> (forall a. TableRow a -> Int)
-> (forall a. Eq a => a -> TableRow a -> Bool)
-> (forall a. Ord a => TableRow a -> a)
-> (forall a. Ord a => TableRow a -> a)
-> (forall a. Num a => TableRow a -> a)
-> (forall a. Num a => TableRow a -> a)
-> Foldable TableRow
forall a. Eq a => a -> TableRow a -> Bool
forall a. Num a => TableRow a -> a
forall a. Ord a => TableRow a -> a
forall m. Monoid m => TableRow m -> m
forall a. TableRow a -> Bool
forall a. TableRow a -> Int
forall a. TableRow a -> [a]
forall a. (a -> a -> a) -> TableRow a -> a
forall m a. Monoid m => (a -> m) -> TableRow a -> m
forall b a. (b -> a -> b) -> b -> TableRow a -> b
forall a b. (a -> b -> b) -> b -> TableRow 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
product :: TableRow a -> a
$cproduct :: forall a. Num a => TableRow a -> a
sum :: TableRow a -> a
$csum :: forall a. Num a => TableRow a -> a
minimum :: TableRow a -> a
$cminimum :: forall a. Ord a => TableRow a -> a
maximum :: TableRow a -> a
$cmaximum :: forall a. Ord a => TableRow a -> a
elem :: a -> TableRow a -> Bool
$celem :: forall a. Eq a => a -> TableRow a -> Bool
length :: TableRow a -> Int
$clength :: forall a. TableRow a -> Int
null :: TableRow a -> Bool
$cnull :: forall a. TableRow a -> Bool
toList :: TableRow a -> [a]
$ctoList :: forall a. TableRow a -> [a]
foldl1 :: (a -> a -> a) -> TableRow a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> TableRow a -> a
foldr1 :: (a -> a -> a) -> TableRow a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> TableRow a -> a
foldl' :: (b -> a -> b) -> b -> TableRow a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> TableRow a -> b
foldl :: (b -> a -> b) -> b -> TableRow a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> TableRow a -> b
foldr' :: (a -> b -> b) -> b -> TableRow a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> TableRow a -> b
foldr :: (a -> b -> b) -> b -> TableRow a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> TableRow a -> b
foldMap' :: (a -> m) -> TableRow a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> TableRow a -> m
foldMap :: (a -> m) -> TableRow a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> TableRow a -> m
fold :: TableRow m -> m
$cfold :: forall m. Monoid m => TableRow m -> m
Foldable,Functor TableRow
Foldable TableRow
Functor TableRow
-> Foldable TableRow
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> TableRow a -> f (TableRow b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    TableRow (f a) -> f (TableRow a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> TableRow a -> m (TableRow b))
-> (forall (m :: * -> *) a.
    Monad m =>
    TableRow (m a) -> m (TableRow a))
-> Traversable TableRow
(a -> f b) -> TableRow a -> f (TableRow b)
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 => TableRow (m a) -> m (TableRow a)
forall (f :: * -> *) a.
Applicative f =>
TableRow (f a) -> f (TableRow a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TableRow a -> m (TableRow b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TableRow a -> f (TableRow b)
sequence :: TableRow (m a) -> m (TableRow a)
$csequence :: forall (m :: * -> *) a. Monad m => TableRow (m a) -> m (TableRow a)
mapM :: (a -> m b) -> TableRow a -> m (TableRow b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TableRow a -> m (TableRow b)
sequenceA :: TableRow (f a) -> f (TableRow a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
TableRow (f a) -> f (TableRow a)
traverse :: (a -> f b) -> TableRow a -> f (TableRow b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TableRow a -> f (TableRow b)
$cp2Traversable :: Foldable TableRow
$cp1Traversable :: Functor TableRow
Traversable)
newtype PredefId = PredefId Id        deriving (PredefId -> PredefId -> Bool
(PredefId -> PredefId -> Bool)
-> (PredefId -> PredefId -> Bool) -> Eq PredefId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PredefId -> PredefId -> Bool
$c/= :: PredefId -> PredefId -> Bool
== :: PredefId -> PredefId -> Bool
$c== :: PredefId -> PredefId -> Bool
Eq,Eq PredefId
Eq PredefId
-> (PredefId -> PredefId -> Ordering)
-> (PredefId -> PredefId -> Bool)
-> (PredefId -> PredefId -> Bool)
-> (PredefId -> PredefId -> Bool)
-> (PredefId -> PredefId -> Bool)
-> (PredefId -> PredefId -> PredefId)
-> (PredefId -> PredefId -> PredefId)
-> Ord PredefId
PredefId -> PredefId -> Bool
PredefId -> PredefId -> Ordering
PredefId -> PredefId -> PredefId
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
min :: PredefId -> PredefId -> PredefId
$cmin :: PredefId -> PredefId -> PredefId
max :: PredefId -> PredefId -> PredefId
$cmax :: PredefId -> PredefId -> PredefId
>= :: PredefId -> PredefId -> Bool
$c>= :: PredefId -> PredefId -> Bool
> :: PredefId -> PredefId -> Bool
$c> :: PredefId -> PredefId -> Bool
<= :: PredefId -> PredefId -> Bool
$c<= :: PredefId -> PredefId -> Bool
< :: PredefId -> PredefId -> Bool
$c< :: PredefId -> PredefId -> Bool
compare :: PredefId -> PredefId -> Ordering
$ccompare :: PredefId -> PredefId -> Ordering
$cp1Ord :: Eq PredefId
Ord,Int -> PredefId -> ShowS
[PredefId] -> ShowS
PredefId -> String
(Int -> PredefId -> ShowS)
-> (PredefId -> String) -> ([PredefId] -> ShowS) -> Show PredefId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PredefId] -> ShowS
$cshowList :: [PredefId] -> ShowS
show :: PredefId -> String
$cshow :: PredefId -> String
showsPrec :: Int -> PredefId -> ShowS
$cshowsPrec :: Int -> PredefId -> ShowS
Show)
newtype LabelId  = LabelId Id         deriving (LabelId -> LabelId -> Bool
(LabelId -> LabelId -> Bool)
-> (LabelId -> LabelId -> Bool) -> Eq LabelId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LabelId -> LabelId -> Bool
$c/= :: LabelId -> LabelId -> Bool
== :: LabelId -> LabelId -> Bool
$c== :: LabelId -> LabelId -> Bool
Eq,Eq LabelId
Eq LabelId
-> (LabelId -> LabelId -> Ordering)
-> (LabelId -> LabelId -> Bool)
-> (LabelId -> LabelId -> Bool)
-> (LabelId -> LabelId -> Bool)
-> (LabelId -> LabelId -> Bool)
-> (LabelId -> LabelId -> LabelId)
-> (LabelId -> LabelId -> LabelId)
-> Ord LabelId
LabelId -> LabelId -> Bool
LabelId -> LabelId -> Ordering
LabelId -> LabelId -> LabelId
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
min :: LabelId -> LabelId -> LabelId
$cmin :: LabelId -> LabelId -> LabelId
max :: LabelId -> LabelId -> LabelId
$cmax :: LabelId -> LabelId -> LabelId
>= :: LabelId -> LabelId -> Bool
$c>= :: LabelId -> LabelId -> Bool
> :: LabelId -> LabelId -> Bool
$c> :: LabelId -> LabelId -> Bool
<= :: LabelId -> LabelId -> Bool
$c<= :: LabelId -> LabelId -> Bool
< :: LabelId -> LabelId -> Bool
$c< :: LabelId -> LabelId -> Bool
compare :: LabelId -> LabelId -> Ordering
$ccompare :: LabelId -> LabelId -> Ordering
$cp1Ord :: Eq LabelId
Ord,Int -> LabelId -> ShowS
[LabelId] -> ShowS
LabelId -> String
(Int -> LabelId -> ShowS)
-> (LabelId -> String) -> ([LabelId] -> ShowS) -> Show LabelId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LabelId] -> ShowS
$cshowList :: [LabelId] -> ShowS
show :: LabelId -> String
$cshow :: LabelId -> String
showsPrec :: Int -> LabelId -> ShowS
$cshowsPrec :: Int -> LabelId -> ShowS
Show)
data VarValueId  = VarValueId QualId  deriving (VarValueId -> VarValueId -> Bool
(VarValueId -> VarValueId -> Bool)
-> (VarValueId -> VarValueId -> Bool) -> Eq VarValueId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VarValueId -> VarValueId -> Bool
$c/= :: VarValueId -> VarValueId -> Bool
== :: VarValueId -> VarValueId -> Bool
$c== :: VarValueId -> VarValueId -> Bool
Eq,Eq VarValueId
Eq VarValueId
-> (VarValueId -> VarValueId -> Ordering)
-> (VarValueId -> VarValueId -> Bool)
-> (VarValueId -> VarValueId -> Bool)
-> (VarValueId -> VarValueId -> Bool)
-> (VarValueId -> VarValueId -> Bool)
-> (VarValueId -> VarValueId -> VarValueId)
-> (VarValueId -> VarValueId -> VarValueId)
-> Ord VarValueId
VarValueId -> VarValueId -> Bool
VarValueId -> VarValueId -> Ordering
VarValueId -> VarValueId -> VarValueId
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
min :: VarValueId -> VarValueId -> VarValueId
$cmin :: VarValueId -> VarValueId -> VarValueId
max :: VarValueId -> VarValueId -> VarValueId
$cmax :: VarValueId -> VarValueId -> VarValueId
>= :: VarValueId -> VarValueId -> Bool
$c>= :: VarValueId -> VarValueId -> Bool
> :: VarValueId -> VarValueId -> Bool
$c> :: VarValueId -> VarValueId -> Bool
<= :: VarValueId -> VarValueId -> Bool
$c<= :: VarValueId -> VarValueId -> Bool
< :: VarValueId -> VarValueId -> Bool
$c< :: VarValueId -> VarValueId -> Bool
compare :: VarValueId -> VarValueId -> Ordering
$ccompare :: VarValueId -> VarValueId -> Ordering
$cp1Ord :: Eq VarValueId
Ord,Int -> VarValueId -> ShowS
[VarValueId] -> ShowS
VarValueId -> String
(Int -> VarValueId -> ShowS)
-> (VarValueId -> String)
-> ([VarValueId] -> ShowS)
-> Show VarValueId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VarValueId] -> ShowS
$cshowList :: [VarValueId] -> ShowS
show :: VarValueId -> String
$cshow :: VarValueId -> String
showsPrec :: Int -> VarValueId -> ShowS
$cshowsPrec :: Int -> VarValueId -> ShowS
Show)
newtype ParamId = ParamId QualId  deriving (ParamId -> ParamId -> Bool
(ParamId -> ParamId -> Bool)
-> (ParamId -> ParamId -> Bool) -> Eq ParamId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParamId -> ParamId -> Bool
$c/= :: ParamId -> ParamId -> Bool
== :: ParamId -> ParamId -> Bool
$c== :: ParamId -> ParamId -> Bool
Eq,Eq ParamId
Eq ParamId
-> (ParamId -> ParamId -> Ordering)
-> (ParamId -> ParamId -> Bool)
-> (ParamId -> ParamId -> Bool)
-> (ParamId -> ParamId -> Bool)
-> (ParamId -> ParamId -> Bool)
-> (ParamId -> ParamId -> ParamId)
-> (ParamId -> ParamId -> ParamId)
-> Ord ParamId
ParamId -> ParamId -> Bool
ParamId -> ParamId -> Ordering
ParamId -> ParamId -> ParamId
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
min :: ParamId -> ParamId -> ParamId
$cmin :: ParamId -> ParamId -> ParamId
max :: ParamId -> ParamId -> ParamId
$cmax :: ParamId -> ParamId -> ParamId
>= :: ParamId -> ParamId -> Bool
$c>= :: ParamId -> ParamId -> Bool
> :: ParamId -> ParamId -> Bool
$c> :: ParamId -> ParamId -> Bool
<= :: ParamId -> ParamId -> Bool
$c<= :: ParamId -> ParamId -> Bool
< :: ParamId -> ParamId -> Bool
$c< :: ParamId -> ParamId -> Bool
compare :: ParamId -> ParamId -> Ordering
$ccompare :: ParamId -> ParamId -> Ordering
$cp1Ord :: Eq ParamId
Ord,Int -> ParamId -> ShowS
[ParamId] -> ShowS
ParamId -> String
(Int -> ParamId -> ShowS)
-> (ParamId -> String) -> ([ParamId] -> ShowS) -> Show ParamId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParamId] -> ShowS
$cshowList :: [ParamId] -> ShowS
show :: ParamId -> String
$cshow :: ParamId -> String
showsPrec :: Int -> ParamId -> ShowS
$cshowsPrec :: Int -> ParamId -> ShowS
Show)
newtype ModId = ModId Id  deriving (ModId -> ModId -> Bool
(ModId -> ModId -> Bool) -> (ModId -> ModId -> Bool) -> Eq ModId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModId -> ModId -> Bool
$c/= :: ModId -> ModId -> Bool
== :: ModId -> ModId -> Bool
$c== :: ModId -> ModId -> Bool
Eq,Eq ModId
Eq ModId
-> (ModId -> ModId -> Ordering)
-> (ModId -> ModId -> Bool)
-> (ModId -> ModId -> Bool)
-> (ModId -> ModId -> Bool)
-> (ModId -> ModId -> Bool)
-> (ModId -> ModId -> ModId)
-> (ModId -> ModId -> ModId)
-> Ord ModId
ModId -> ModId -> Bool
ModId -> ModId -> Ordering
ModId -> ModId -> ModId
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
min :: ModId -> ModId -> ModId
$cmin :: ModId -> ModId -> ModId
max :: ModId -> ModId -> ModId
$cmax :: ModId -> ModId -> ModId
>= :: ModId -> ModId -> Bool
$c>= :: ModId -> ModId -> Bool
> :: ModId -> ModId -> Bool
$c> :: ModId -> ModId -> Bool
<= :: ModId -> ModId -> Bool
$c<= :: ModId -> ModId -> Bool
< :: ModId -> ModId -> Bool
$c< :: ModId -> ModId -> Bool
compare :: ModId -> ModId -> Ordering
$ccompare :: ModId -> ModId -> Ordering
$cp1Ord :: Eq ModId
Ord,Int -> ModId -> ShowS
[ModId] -> ShowS
ModId -> String
(Int -> ModId -> ShowS)
-> (ModId -> String) -> ([ModId] -> ShowS) -> Show ModId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModId] -> ShowS
$cshowList :: [ModId] -> ShowS
show :: ModId -> String
$cshow :: ModId -> String
showsPrec :: Int -> ModId -> ShowS
$cshowsPrec :: Int -> ModId -> ShowS
Show)
newtype CatId = CatId Id  deriving (CatId -> CatId -> Bool
(CatId -> CatId -> Bool) -> (CatId -> CatId -> Bool) -> Eq CatId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CatId -> CatId -> Bool
$c/= :: CatId -> CatId -> Bool
== :: CatId -> CatId -> Bool
$c== :: CatId -> CatId -> Bool
Eq,Eq CatId
Eq CatId
-> (CatId -> CatId -> Ordering)
-> (CatId -> CatId -> Bool)
-> (CatId -> CatId -> Bool)
-> (CatId -> CatId -> Bool)
-> (CatId -> CatId -> Bool)
-> (CatId -> CatId -> CatId)
-> (CatId -> CatId -> CatId)
-> Ord CatId
CatId -> CatId -> Bool
CatId -> CatId -> Ordering
CatId -> CatId -> CatId
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
min :: CatId -> CatId -> CatId
$cmin :: CatId -> CatId -> CatId
max :: CatId -> CatId -> CatId
$cmax :: CatId -> CatId -> CatId
>= :: CatId -> CatId -> Bool
$c>= :: CatId -> CatId -> Bool
> :: CatId -> CatId -> Bool
$c> :: CatId -> CatId -> Bool
<= :: CatId -> CatId -> Bool
$c<= :: CatId -> CatId -> Bool
< :: CatId -> CatId -> Bool
$c< :: CatId -> CatId -> Bool
compare :: CatId -> CatId -> Ordering
$ccompare :: CatId -> CatId -> Ordering
$cp1Ord :: Eq CatId
Ord,Int -> CatId -> ShowS
[CatId] -> ShowS
CatId -> String
(Int -> CatId -> ShowS)
-> (CatId -> String) -> ([CatId] -> ShowS) -> Show CatId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CatId] -> ShowS
$cshowList :: [CatId] -> ShowS
show :: CatId -> String
$cshow :: CatId -> String
showsPrec :: Int -> CatId -> ShowS
$cshowsPrec :: Int -> CatId -> ShowS
Show)
newtype FunId = FunId Id  deriving (FunId -> FunId -> Bool
(FunId -> FunId -> Bool) -> (FunId -> FunId -> Bool) -> Eq FunId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FunId -> FunId -> Bool
$c/= :: FunId -> FunId -> Bool
== :: FunId -> FunId -> Bool
$c== :: FunId -> FunId -> Bool
Eq,Int -> FunId -> ShowS
[FunId] -> ShowS
FunId -> String
(Int -> FunId -> ShowS)
-> (FunId -> String) -> ([FunId] -> ShowS) -> Show FunId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FunId] -> ShowS
$cshowList :: [FunId] -> ShowS
show :: FunId -> String
$cshow :: FunId -> String
showsPrec :: Int -> FunId -> ShowS
$cshowsPrec :: Int -> FunId -> ShowS
Show)
data VarId = Anonymous | VarId Id  deriving Int -> VarId -> ShowS
[VarId] -> ShowS
VarId -> String
(Int -> VarId -> ShowS)
-> (VarId -> String) -> ([VarId] -> ShowS) -> Show VarId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VarId] -> ShowS
$cshowList :: [VarId] -> ShowS
show :: VarId -> String
$cshow :: VarId -> String
showsPrec :: Int -> VarId -> ShowS
$cshowsPrec :: Int -> VarId -> ShowS
Show
newtype Flags = Flags [(FlagName,FlagValue)] deriving Int -> Flags -> ShowS
[Flags] -> ShowS
Flags -> String
(Int -> Flags -> ShowS)
-> (Flags -> String) -> ([Flags] -> ShowS) -> Show Flags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Flags] -> ShowS
$cshowList :: [Flags] -> ShowS
show :: Flags -> String
$cshow :: Flags -> String
showsPrec :: Int -> Flags -> ShowS
$cshowsPrec :: Int -> Flags -> ShowS
Show
type FlagName = Id
data FlagValue = Str String | Int Int | Flt Double deriving Int -> FlagValue -> ShowS
[FlagValue] -> ShowS
FlagValue -> String
(Int -> FlagValue -> ShowS)
-> (FlagValue -> String)
-> ([FlagValue] -> ShowS)
-> Show FlagValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FlagValue] -> ShowS
$cshowList :: [FlagValue] -> ShowS
show :: FlagValue -> String
$cshow :: FlagValue -> String
showsPrec :: Int -> FlagValue -> ShowS
$cshowsPrec :: Int -> FlagValue -> ShowS
Show
type Id = RawIdent
data QualId = Qual ModId Id | Unqual Id  deriving (QualId -> QualId -> Bool
(QualId -> QualId -> Bool)
-> (QualId -> QualId -> Bool) -> Eq QualId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QualId -> QualId -> Bool
$c/= :: QualId -> QualId -> Bool
== :: QualId -> QualId -> Bool
$c== :: QualId -> QualId -> Bool
Eq,Eq QualId
Eq QualId
-> (QualId -> QualId -> Ordering)
-> (QualId -> QualId -> Bool)
-> (QualId -> QualId -> Bool)
-> (QualId -> QualId -> Bool)
-> (QualId -> QualId -> Bool)
-> (QualId -> QualId -> QualId)
-> (QualId -> QualId -> QualId)
-> Ord QualId
QualId -> QualId -> Bool
QualId -> QualId -> Ordering
QualId -> QualId -> QualId
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
min :: QualId -> QualId -> QualId
$cmin :: QualId -> QualId -> QualId
max :: QualId -> QualId -> QualId
$cmax :: QualId -> QualId -> QualId
>= :: QualId -> QualId -> Bool
$c>= :: QualId -> QualId -> Bool
> :: QualId -> QualId -> Bool
$c> :: QualId -> QualId -> Bool
<= :: QualId -> QualId -> Bool
$c<= :: QualId -> QualId -> Bool
< :: QualId -> QualId -> Bool
$c< :: QualId -> QualId -> Bool
compare :: QualId -> QualId -> Ordering
$ccompare :: QualId -> QualId -> Ordering
$cp1Ord :: Eq QualId
Ord,Int -> QualId -> ShowS
[QualId] -> ShowS
QualId -> String
(Int -> QualId -> ShowS)
-> (QualId -> String) -> ([QualId] -> ShowS) -> Show QualId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QualId] -> ShowS
$cshowList :: [QualId] -> ShowS
show :: QualId -> String
$cshow :: QualId -> String
showsPrec :: Int -> QualId -> ShowS
$cshowsPrec :: Int -> QualId -> ShowS
Show)
instance Pretty Grammar where
  pp :: Grammar -> Doc
pp (Grammar Abstract
abs [Concrete]
cncs) = Abstract
abs Abstract -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
$+$ [Concrete] -> Doc
forall a. Pretty a => [a] -> Doc
vcat [Concrete]
cncs
instance Pretty Abstract where
  pp :: Abstract -> Doc
pp (Abstract ModId
m Flags
flags [CatDef]
cats [FunDef]
funs) =
    String
"abstract" String -> ModId -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> ModId
m Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"=" Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"{" Doc -> Flags -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
$$
       Flags
flags Doc -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
$$
       String
"cat" String -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> [CatDef] -> Doc
forall a. Pretty a => [a] -> Doc
fsep [CatDef]
cats Doc -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
$$
       String
"fun" String -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> [FunDef] -> Doc
forall a. Pretty a => [a] -> Doc
vcat [FunDef]
funs Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
$$
       String
"}"
instance Pretty CatDef where
  pp :: CatDef -> Doc
pp (CatDef CatId
c [CatId]
cs) = [CatId] -> Doc
forall a. Pretty a => [a] -> Doc
hsep (CatId
cCatId -> [CatId] -> [CatId]
forall a. a -> [a] -> [a]
:[CatId]
cs)Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String
";"
instance Pretty FunDef where
  pp :: FunDef -> Doc
pp (FunDef FunId
f Type
ty) = FunId
f FunId -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
":" Doc -> Type -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> Type
ty Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String
";"
instance Pretty Type where
  pp :: Type -> Doc
pp (Type [TypeBinding]
bs TypeApp
ty) = [Doc] -> Doc
forall a. Pretty a => [a] -> Doc
sep (String -> [Doc] -> [Doc]
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> [a2] -> [Doc]
punctuate String
" ->" ((TypeBinding -> Doc) -> [TypeBinding] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map TypeBinding -> Doc
forall a. Pretty a => a -> Doc
pp [TypeBinding]
bs [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [TypeApp -> Doc
forall a. Pretty a => a -> Doc
pp TypeApp
ty]))
instance PPA Type where
  ppA :: Type -> Doc
ppA (Type [] (TypeApp CatId
c [])) = CatId -> Doc
forall a. Pretty a => a -> Doc
pp CatId
c
  ppA Type
t = Type -> Doc
forall a. Pretty a => a -> Doc
parens Type
t
instance Pretty TypeBinding where
  pp :: TypeBinding -> Doc
pp (TypeBinding VarId
Anonymous (Type [] TypeApp
tapp)) = TypeApp -> Doc
forall a. Pretty a => a -> Doc
pp TypeApp
tapp
  pp (TypeBinding VarId
Anonymous Type
ty) = Type -> Doc
forall a. Pretty a => a -> Doc
parens Type
ty
  pp (TypeBinding (VarId Id
x) Type
ty) = Doc -> Doc
forall a. Pretty a => a -> Doc
parens (Id
xId -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>String
":"Doc -> Type -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>Type
ty)
instance Pretty TypeApp where
 pp :: TypeApp -> Doc
pp (TypeApp CatId
c [Type]
targs) = CatId
cCatId -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>[Doc] -> Doc
forall a. Pretty a => [a] -> Doc
hsep ((Type -> Doc) -> [Type] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Type -> Doc
forall a. PPA a => a -> Doc
ppA [Type]
targs)
instance Pretty VarId where
  pp :: VarId -> Doc
pp VarId
Anonymous = String -> Doc
forall a. Pretty a => a -> Doc
pp String
"_"
  pp (VarId Id
x) = Id -> Doc
forall a. Pretty a => a -> Doc
pp Id
x
instance Pretty Concrete where
  pp :: Concrete -> Doc
pp (Concrete ModId
cncid ModId
absid Flags
flags [ParamDef]
params [LincatDef]
lincats [LinDef]
lins) =
      String
"concrete" String -> ModId -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> ModId
cncid Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"of" Doc -> ModId -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> ModId
absid Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"=" Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"{" Doc -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
$$
      [ParamDef] -> Doc
forall a. Pretty a => [a] -> Doc
vcat [ParamDef]
params Doc -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
$$
      String -> [LincatDef] -> Doc
forall a1 a1. (Pretty a1, Pretty a1) => a1 -> [a1] -> Doc
section String
"lincat" [LincatDef]
lincats Doc -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
$$
      String -> [LinDef] -> Doc
forall a1 a1. (Pretty a1, Pretty a1) => a1 -> [a1] -> Doc
section String
"lin" [LinDef]
lins Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
$$
      String
"}"
    where
      section :: a1 -> [a1] -> Doc
section a1
name [] = Doc
empty
      section a1
name [a1]
ds = a1
name a1 -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> [Doc] -> Doc
forall a. Pretty a => [a] -> Doc
vcat ((a1 -> Doc) -> [a1] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (a1 -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<> String
";") [a1]
ds)
instance Pretty ParamDef where
  pp :: ParamDef -> Doc
pp (ParamDef ParamId
p [ParamValueDef]
pvs) = Doc -> Int -> [Doc] -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> Int -> a2 -> Doc
hang (String
"param"String -> ParamId -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> ParamId
p Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"=") Int
4 (String -> [ParamValueDef] -> [Doc]
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> [a2] -> [Doc]
punctuate String
" |" [ParamValueDef]
pvs)Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String
";"
  pp (ParamAliasDef ParamId
p LinType
t) = Doc -> Int -> LinType -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> Int -> a2 -> Doc
hang (String
"oper"String -> ParamId -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> ParamId
p Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"=") Int
4 LinType
tDoc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String
";"
instance PPA arg => Pretty (Param arg) where
  pp :: Param arg -> Doc
pp (Param ParamId
p [arg]
ps) = ParamId -> Doc
forall a. Pretty a => a -> Doc
pp ParamId
pDoc -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>[Doc] -> Doc
forall a. Pretty a => [a] -> Doc
sep ((arg -> Doc) -> [arg] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map arg -> Doc
forall a. PPA a => a -> Doc
ppA [arg]
ps)
instance PPA arg => PPA (Param arg) where
  ppA :: Param arg -> Doc
ppA (Param ParamId
p []) = ParamId -> Doc
forall a. Pretty a => a -> Doc
pp ParamId
p
  ppA Param arg
pv = Param arg -> Doc
forall a. Pretty a => a -> Doc
parens Param arg
pv
instance Pretty LincatDef where
  pp :: LincatDef -> Doc
pp (LincatDef CatId
c LinType
lt) = Doc -> Int -> LinType -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> Int -> a2 -> Doc
hang (CatId
c CatId -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"=") Int
4 LinType
lt
instance Pretty LinType where
 pp :: LinType -> Doc
pp LinType
lt = case LinType
lt of
           LinType
FloatType -> String -> Doc
forall a. Pretty a => a -> Doc
pp String
"Float"
           LinType
IntType -> String -> Doc
forall a. Pretty a => a -> Doc
pp String
"Int"
           ParamType ParamType
pt -> ParamType -> Doc
forall a. Pretty a => a -> Doc
pp ParamType
pt
           RecordType [RecordRowType]
rs -> [RecordRowType] -> Doc
forall a. Pretty a => [a] -> Doc
block [RecordRowType]
rs
           LinType
StrType -> String -> Doc
forall a. Pretty a => a -> Doc
pp String
"Str"
           TableType LinType
pt LinType
lt -> [Doc] -> Doc
forall a. Pretty a => [a] -> Doc
sep [LinType
pt LinType -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"=>",LinType -> Doc
forall a. Pretty a => a -> Doc
pp LinType
lt]
           TupleType [LinType]
lts -> String
"<"String -> [Doc] -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String -> [LinType] -> [Doc]
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> [a2] -> [Doc]
punctuate String
"," [LinType]
ltsDoc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String
">"
instance RhsSeparator LinType  where rhsSep :: LinType -> Doc
rhsSep LinType
_ = String -> Doc
forall a. Pretty a => a -> Doc
pp String
":"
instance Pretty ParamType where
  pp :: ParamType -> Doc
pp (ParamTypeId ParamId
p) = ParamId -> Doc
forall a. Pretty a => a -> Doc
pp ParamId
p
instance Pretty LinDef where
  pp :: LinDef -> Doc
pp (LinDef FunId
f [VarId]
xs LinValue
lv) = Doc -> Int -> LinValue -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> Int -> a2 -> Doc
hang (FunId
fFunId -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>[VarId] -> Doc
forall a. Pretty a => [a] -> Doc
hsep [VarId]
xsDoc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>String
"=") Int
4 LinValue
lv
instance Pretty LinValue where
  pp :: LinValue -> Doc
pp LinValue
lv = case LinValue
lv of
            ConcatValue LinValue
v1 LinValue
v2 -> [Doc] -> Doc
forall a. Pretty a => [a] -> Doc
sep [LinValue
v1 LinValue -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"++",LinValue -> Doc
forall a. Pretty a => a -> Doc
pp LinValue
v2]
            ErrorValue String
s -> String
"Predef.error"String -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>String -> Doc
forall a. Pretty a => a -> Doc
doubleQuotes String
s
            ParamConstant ParamValue
pv -> ParamValue -> Doc
forall a. Pretty a => a -> Doc
pp ParamValue
pv
            Projection LinValue
lv LabelId
l -> LinValue -> Doc
forall a. PPA a => a -> Doc
ppA LinValue
lvDoc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String
"."Doc -> LabelId -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>LabelId
l
            Selection LinValue
tv LinValue
pv -> LinValue -> Doc
forall a. PPA a => a -> Doc
ppA LinValue
tvDoc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String
"!"Doc -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>LinValue -> Doc
forall a. PPA a => a -> Doc
ppA LinValue
pv
            VariantValue [LinValue]
vs -> String
"variants"String -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>[LinValue] -> Doc
forall a. Pretty a => [a] -> Doc
block [LinValue]
vs
            CommentedValue String
s LinValue
v -> String
"{-" String -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
s Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"-}" Doc -> LinValue -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
$$ LinValue
v
            LinValue
_ -> LinValue -> Doc
forall a. PPA a => a -> Doc
ppA LinValue
lv
instance PPA LinValue where
  ppA :: LinValue -> Doc
ppA LinValue
lv = case LinValue
lv of
             LiteralValue LinLiteral
l -> LinLiteral -> Doc
forall a. PPA a => a -> Doc
ppA LinLiteral
l
             ParamConstant ParamValue
pv -> ParamValue -> Doc
forall a. PPA a => a -> Doc
ppA ParamValue
pv
             PredefValue PredefId
p -> PredefId -> Doc
forall a. PPA a => a -> Doc
ppA PredefId
p
             RecordValue [] -> String -> Doc
forall a. Pretty a => a -> Doc
pp String
"<>"
             RecordValue [RecordRowValue]
rvs -> [RecordRowValue] -> Doc
forall a. Pretty a => [a] -> Doc
block [RecordRowValue]
rvs
             PreValue [([String], LinValue)]
alts LinValue
def ->
               String
"pre"String -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>[Doc] -> Doc
forall a. Pretty a => [a] -> Doc
block ((([String], LinValue) -> Doc) -> [([String], LinValue)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ([String], LinValue) -> Doc
forall a a2. (Pretty a, Pretty a2) => ([a], a2) -> Doc
alt [([String], LinValue)]
alts[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++[String
"_"String -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>String
"=>"Doc -> LinValue -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>LinValue
def])
               where
                 alt :: ([a], a2) -> Doc
alt ([a]
ss,a2
lv) = Doc -> Int -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> Int -> a2 -> Doc
hang ([Doc] -> Doc
forall a. Pretty a => [a] -> Doc
hcat (String -> [Doc] -> [Doc]
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> [a2] -> [Doc]
punctuate String
"|" ((a -> Doc) -> [a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map a -> Doc
forall a. Pretty a => a -> Doc
doubleQuotes [a]
ss)))
                                    Int
2 (String
"=>"String -> a2 -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>a2
lv)
             TableValue LinType
_ [TableRowValue]
tvs -> String
"table"String -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>[TableRowValue] -> Doc
forall a. Pretty a => [a] -> Doc
block [TableRowValue]
tvs
             TupleValue [LinValue]
lvs -> String
"<"String -> [Doc] -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String -> [LinValue] -> [Doc]
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> [a2] -> [Doc]
punctuate String
"," [LinValue]
lvsDoc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String
">"
             VarValue VarValueId
v -> VarValueId -> Doc
forall a. Pretty a => a -> Doc
pp VarValueId
v
             LinValue
_ -> LinValue -> Doc
forall a. Pretty a => a -> Doc
parens LinValue
lv
instance Pretty LinLiteral where pp :: LinLiteral -> Doc
pp = LinLiteral -> Doc
forall a. PPA a => a -> Doc
ppA
instance PPA LinLiteral where
  ppA :: LinLiteral -> Doc
ppA LinLiteral
l = case LinLiteral
l of
            FloatConstant Float
f -> Float -> Doc
forall a. Pretty a => a -> Doc
pp Float
f
            IntConstant Int
n -> Int -> Doc
forall a. Pretty a => a -> Doc
pp Int
n
            StrConstant String
s -> String -> Doc
forall a. Pretty a => a -> Doc
doubleQuotes String
s 
instance RhsSeparator LinValue where rhsSep :: LinValue -> Doc
rhsSep LinValue
_ = String -> Doc
forall a. Pretty a => a -> Doc
pp String
"="
instance Pretty LinPattern where
  pp :: LinPattern -> Doc
pp LinPattern
p =
    case LinPattern
p of
      ParamPattern ParamPattern
pv -> ParamPattern -> Doc
forall a. Pretty a => a -> Doc
pp ParamPattern
pv
      LinPattern
_ -> LinPattern -> Doc
forall a. PPA a => a -> Doc
ppA LinPattern
p
instance PPA LinPattern where
  ppA :: LinPattern -> Doc
ppA LinPattern
p =
    case LinPattern
p of
      ParamPattern ParamPattern
pv -> ParamPattern -> Doc
forall a. PPA a => a -> Doc
ppA ParamPattern
pv
      RecordPattern [RecordRow LinPattern]
r -> [RecordRow LinPattern] -> Doc
forall a. Pretty a => [a] -> Doc
block [RecordRow LinPattern]
r
      TuplePattern [LinPattern]
ps -> String
"<"String -> [Doc] -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String -> [LinPattern] -> [Doc]
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> [a2] -> [Doc]
punctuate String
"," [LinPattern]
psDoc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String
">"
      LinPattern
WildPattern     -> String -> Doc
forall a. Pretty a => a -> Doc
pp String
"_"
instance RhsSeparator LinPattern where rhsSep :: LinPattern -> Doc
rhsSep LinPattern
_ = String -> Doc
forall a. Pretty a => a -> Doc
pp String
"="
instance RhsSeparator rhs => Pretty (RecordRow rhs) where
  pp :: RecordRow rhs -> Doc
pp (RecordRow LabelId
l rhs
v) = Doc -> Int -> rhs -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> Int -> a2 -> Doc
hang (LabelId
lLabelId -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>rhs -> Doc
forall rhs. RhsSeparator rhs => rhs -> Doc
rhsSep rhs
v) Int
2 rhs
v
instance Pretty rhs => Pretty (TableRow rhs) where
  pp :: TableRow rhs -> Doc
pp (TableRow LinPattern
l rhs
v) = Doc -> Int -> rhs -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> Int -> a2 -> Doc
hang (LinPattern
lLinPattern -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+>String
"=>") Int
2 rhs
v
instance Pretty ModId where pp :: ModId -> Doc
pp (ModId Id
s) = Id -> Doc
forall a. Pretty a => a -> Doc
pp Id
s
instance Pretty CatId where pp :: CatId -> Doc
pp (CatId Id
s) = Id -> Doc
forall a. Pretty a => a -> Doc
pp Id
s
instance Pretty FunId where pp :: FunId -> Doc
pp (FunId Id
s) = Id -> Doc
forall a. Pretty a => a -> Doc
pp Id
s
instance Pretty LabelId where pp :: LabelId -> Doc
pp (LabelId Id
s) = Id -> Doc
forall a. Pretty a => a -> Doc
pp Id
s
instance Pretty PredefId where pp :: PredefId -> Doc
pp = PredefId -> Doc
forall a. PPA a => a -> Doc
ppA
instance PPA    PredefId where ppA :: PredefId -> Doc
ppA (PredefId Id
s) = String
"Predef."String -> Id -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>Id
s
instance Pretty ParamId where pp :: ParamId -> Doc
pp = ParamId -> Doc
forall a. PPA a => a -> Doc
ppA
instance PPA    ParamId where ppA :: ParamId -> Doc
ppA (ParamId QualId
s) = QualId -> Doc
forall a. Pretty a => a -> Doc
pp QualId
s
instance Pretty VarValueId where pp :: VarValueId -> Doc
pp (VarValueId QualId
s) = QualId -> Doc
forall a. Pretty a => a -> Doc
pp QualId
s
instance Pretty QualId where pp :: QualId -> Doc
pp = QualId -> Doc
forall a. PPA a => a -> Doc
ppA
instance PPA QualId where
  ppA :: QualId -> Doc
ppA (Qual ModId
m Id
n) = ModId
mModId -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String
"_"Doc -> Id -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>Id
n 
  ppA (Unqual Id
n) = Id -> Doc
forall a. Pretty a => a -> Doc
pp Id
n
instance Pretty Flags where
  pp :: Flags -> Doc
pp (Flags []) = Doc
empty
  pp (Flags [(Id, FlagValue)]
flags) = String
"flags" String -> Doc -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> [Doc] -> Doc
forall a. Pretty a => [a] -> Doc
vcat (((Id, FlagValue) -> Doc) -> [(Id, FlagValue)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Id, FlagValue) -> Doc
forall a2 a1. (Pretty a2, Pretty a1) => (a1, a2) -> Doc
ppFlag [(Id, FlagValue)]
flags)
    where
      ppFlag :: (a1, a2) -> Doc
ppFlag (a1
name,a2
value) = a1
name a1 -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> String
"=" Doc -> a2 -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<+> a2
value Doc -> String -> Doc
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> a2 -> Doc
<>String
";"
instance Pretty FlagValue where
  pp :: FlagValue -> Doc
pp (Str String
s) = String -> Doc
forall a. Pretty a => a -> Doc
pp String
s
  pp (Int Int
i) = Int -> Doc
forall a. Pretty a => a -> Doc
pp Int
i
  pp (Flt Double
d) = Double -> Doc
forall a. Pretty a => a -> Doc
pp Double
d
class Pretty a => PPA a where ppA :: a -> Doc
class Pretty rhs => RhsSeparator rhs where rhsSep :: rhs -> Doc
semiSep :: [a2] -> [Doc]
semiSep [a2]
xs = String -> [a2] -> [Doc]
forall a1 a2. (Pretty a1, Pretty a2) => a1 -> [a2] -> [Doc]
punctuate String
";" [a2]
xs
block :: [a2] -> Doc
block [a2]
xs = [Doc] -> Doc
forall a. Pretty a => a -> Doc
braces ([a2] -> [Doc]
forall a2. Pretty a2 => [a2] -> [Doc]
semiSep [a2]
xs)