disco-0.2: Functional programming language for teaching discrete math.
Copyrightdisco team and contributors
LicenseBSD-3-Clause
Maintainerbyorgey@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Disco.AST.Core

Contents

Description

Abstract syntax trees representing the desugared, untyped core language for Disco.

Synopsis

Core AST

data ShouldMemo Source #

Constructors

Memo 
NoMemo 

Instances

Instances details
Data ShouldMemo Source # 
Instance details

Defined in Disco.AST.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShouldMemo -> c ShouldMemo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShouldMemo #

toConstr :: ShouldMemo -> Constr #

dataTypeOf :: ShouldMemo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ShouldMemo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShouldMemo) #

gmapT :: (forall b. Data b => b -> b) -> ShouldMemo -> ShouldMemo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShouldMemo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShouldMemo -> r #

gmapQ :: (forall d. Data d => d -> u) -> ShouldMemo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ShouldMemo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShouldMemo -> m ShouldMemo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShouldMemo -> m ShouldMemo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShouldMemo -> m ShouldMemo #

Generic ShouldMemo Source # 
Instance details

Defined in Disco.AST.Core

Associated Types

type Rep ShouldMemo :: Type -> Type #

Show ShouldMemo Source # 
Instance details

Defined in Disco.AST.Core

Alpha ShouldMemo Source # 
Instance details

Defined in Disco.AST.Core

type Rep ShouldMemo Source # 
Instance details

Defined in Disco.AST.Core

type Rep ShouldMemo = D1 ('MetaData "ShouldMemo" "Disco.AST.Core" "disco-0.2-Ic5OYLGQ1QL1sNsEHodldc" 'False) (C1 ('MetaCons "Memo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoMemo" 'PrefixI 'False) (U1 :: Type -> Type))

data Core where Source #

AST for the desugared, untyped core language.

Constructors

CVar :: QName Core -> Core

A variable.

CNum :: Rational -> Core

A rational number.

CConst :: Op -> Core

A built-in constant.

CInj :: Side -> Core -> Core

An injection into a sum type, i.e. a value together with a tag indicating which element of a sum type we are in. For example, false is represented by CSum L CUnit; right(v) is represented by CSum R v. Note we do not need to remember which type the constructor came from; if the program typechecked then we will never end up comparing constructors from different types.

CCase :: Core -> Bind (Name Core) Core -> Bind (Name Core) Core -> Core

A primitive case expression on a value of a sum type.

CUnit :: Core

The unit value.

CPair :: Core -> Core -> Core

A pair of values.

CProj :: Side -> Core -> Core

A projection from a product type, i.e. fst or snd.

CAbs :: ShouldMemo -> Bind [Name Core] Core -> Core

An anonymous function.

CApp :: Core -> Core -> Core

Function application.

CTest :: [(String, Type, Name Core)] -> Core -> Core

A "test frame" under which a test case is run. Records the types and legible names of the variables that should be reported to the user if the test fails.

CType :: Type -> Core

A type.

CDelay :: Bind [Name Core] [Core] -> Core

Introduction form for a lazily evaluated value of type Lazy T for some type T. We can have multiple bindings to multiple terms to create a simple target for compiling mutual recursion.

CForce :: Core -> Core

Force evaluation of a lazy value.

Instances

Instances details
Data Core Source # 
Instance details

Defined in Disco.AST.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Core -> c Core #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Core #

toConstr :: Core -> Constr #

dataTypeOf :: Core -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Core) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Core) #

gmapT :: (forall b. Data b => b -> b) -> Core -> Core #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Core -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Core -> r #

gmapQ :: (forall d. Data d => d -> u) -> Core -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Core -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Core -> m Core #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Core -> m Core #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Core -> m Core #

Generic Core Source # 
Instance details

Defined in Disco.AST.Core

Associated Types

type Rep Core :: Type -> Type #

Methods

from :: Core -> Rep Core x #

to :: Rep Core x -> Core #

Show Core Source # 
Instance details

Defined in Disco.AST.Core

Methods

showsPrec :: Int -> Core -> ShowS #

show :: Core -> String #

showList :: [Core] -> ShowS #

Pretty Core Source # 
Instance details

Defined in Disco.AST.Core

Methods

pretty :: forall (r :: EffectRow) ann. Members '[Reader PA, LFresh] r => Core -> Sem r (Doc ann) Source #

Plated Core Source # 
Instance details

Defined in Disco.AST.Core

Alpha Core Source # 
Instance details

Defined in Disco.AST.Core

type Rep Core Source # 
Instance details

Defined in Disco.AST.Core

type Rep Core = D1 ('MetaData "Core" "Disco.AST.Core" "disco-0.2-Ic5OYLGQ1QL1sNsEHodldc" 'False) (((C1 ('MetaCons "CVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName Core))) :+: (C1 ('MetaCons "CNum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)) :+: C1 ('MetaCons "CConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Op)))) :+: ((C1 ('MetaCons "CInj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Side) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core)) :+: C1 ('MetaCons "CCase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bind (Name Core) Core)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bind (Name Core) Core))))) :+: (C1 ('MetaCons "CUnit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CPair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core))))) :+: ((C1 ('MetaCons "CProj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Side) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core)) :+: (C1 ('MetaCons "CAbs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShouldMemo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bind [Name Core] Core))) :+: C1 ('MetaCons "CApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core)))) :+: ((C1 ('MetaCons "CTest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, Type, Name Core)]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core)) :+: C1 ('MetaCons "CType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: (C1 ('MetaCons "CDelay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bind [Name Core] [Core]))) :+: C1 ('MetaCons "CForce" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core))))))

data Op Source #

Operators that can show up in the core language. Note that not all surface language operators show up here, since some are desugared into combinators of the operators here.

Constructors

OAdd

Addition (+)

ONeg

Arithmetic negation (-)

OSqrt

Integer square root (sqrt)

OFloor

Floor of fractional type (floor)

OCeil

Ceiling of fractional type (ceiling)

OAbs

Absolute value (abs)

OMul

Multiplication (*)

ODiv

Division (/)

OExp

Exponentiation (^)

OMod

Modulo (mod)

ODivides

Divisibility test (|)

OMultinom

Multinomial coefficient (choose)

OFact

Factorial (!)

OEq

Equality test (==)

OLt

Less than (<)

OEnum

Enumerate the values of a type.

OCount

Count the values of a type.

OPower

Power setbag of a given setbag (power).

OBagElem

Set/bag element test.

OListElem

List element test.

OEachBag

Map a function over a bag. Carries the output type of the function.

OEachSet

Map a function over a set. Carries the output type of the function.

OFilterBag

Filter a bag.

OMerge

Merge two bags/sets.

OBagUnions

Bag join, i.e. union a bag of bags.

OSummary

Adjacency List of given graph

OEmptyGraph

Empty graph

OVertex

Construct a vertex with given value

OOverlay

Graph overlay

OConnect

Graph connect

OInsert

Map insert

OLookup

Map lookup

OUntil

Continue until end, [x, y, z .. e]

OSetToList

set -> list conversion (sorted order).

OBagToSet

bag -> set conversion (forget duplicates).

OBagToList

bag -> list conversion (sorted order).

OListToSet

list -> set conversion (forget order, duplicates).

OListToBag

list -> bag conversion (forget order).

OBagToCounts

bag -> set of counts

OCountsToBag

set of counts -> bag

OUnsafeCountsToBag

unsafe set of counts -> bag, assumes all are distinct

OMapToSet

Map k v -> Set (k × v)

OSetToMap

Set (k × v) -> Map k v

OIsPrime

Primality test

OFactor

Factorization

OFrac

Turn a rational into a (num, denom) pair

OForall [Type]

Universal quantification. Applied to a closure t1, ..., tn -> Prop it yields a Prop.

OExists [Type]

Existential quantification. Applied to a closure t1, ..., tn -> Prop it yields a Prop.

OHolds

Convert Prop -> Bool via exhaustive search.

ONotProp

Flip success and failure for a prop.

OShould BOp Type

Comparison assertion

OMatchErr

Error for non-exhaustive pattern match

OCrash

Crash with a user-supplied message

OId

No-op/identity function

OLookupSeq

Lookup OEIS sequence

OExtendSeq

Extend a List via OEIS

OAnd

Not the Boolean And, but instead a propositional BOp | Should only be seen and used with Props.

OOr

Not the Boolean Or, but instead a propositional BOp | Should only be seen and used with Props.

OImpl

Not the Boolean Impl, but instead a propositional BOp | Should only be seen and used with Props.

OSeed 
ORandom 

Instances

Instances details
Data Op Source # 
Instance details

Defined in Disco.AST.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Op -> c Op #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Op #

toConstr :: Op -> Constr #

dataTypeOf :: Op -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Op) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Op) #

gmapT :: (forall b. Data b => b -> b) -> Op -> Op #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r #

gmapQ :: (forall d. Data d => d -> u) -> Op -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Op -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Op -> m Op #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op #

Generic Op Source # 
Instance details

Defined in Disco.AST.Core

Associated Types

type Rep Op :: Type -> Type #

Methods

from :: Op -> Rep Op x #

to :: Rep Op x -> Op #

Show Op Source # 
Instance details

Defined in Disco.AST.Core

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

Pretty Op Source # 
Instance details

Defined in Disco.AST.Core

Methods

pretty :: forall (r :: EffectRow) ann. Members '[Reader PA, LFresh] r => Op -> Sem r (Doc ann) Source #

Eq Op Source # 
Instance details

Defined in Disco.AST.Core

Methods

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

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

Ord Op Source # 
Instance details

Defined in Disco.AST.Core

Methods

compare :: Op -> Op -> Ordering #

(<) :: Op -> Op -> Bool #

(<=) :: Op -> Op -> Bool #

(>) :: Op -> Op -> Bool #

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

max :: Op -> Op -> Op #

min :: Op -> Op -> Op #

Alpha Op Source # 
Instance details

Defined in Disco.AST.Core

type Rep Op Source # 
Instance details

Defined in Disco.AST.Core

type Rep Op = D1 ('MetaData "Op" "Disco.AST.Core" "disco-0.2-Ic5OYLGQ1QL1sNsEHodldc" 'False) (((((C1 ('MetaCons "OAdd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ONeg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OSqrt" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OFloor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OCeil" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OAbs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OMul" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ODiv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OExp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OMod" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ODivides" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OMultinom" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OFact" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OLt" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "OEnum" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OCount" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OPower" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OBagElem" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OListElem" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OEachBag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OEachSet" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "OFilterBag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OMerge" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OBagUnions" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OSummary" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OEmptyGraph" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OVertex" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OOverlay" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OConnect" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "OInsert" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OLookup" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OUntil" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OSetToList" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OBagToSet" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OBagToList" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OListToSet" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "OListToBag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OBagToCounts" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OCountsToBag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OUnsafeCountsToBag" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OMapToSet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OSetToMap" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OIsPrime" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OFactor" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "OFrac" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OForall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type]))) :+: (C1 ('MetaCons "OExists" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type])) :+: C1 ('MetaCons "OHolds" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ONotProp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OShould" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: (C1 ('MetaCons "OMatchErr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OCrash" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "OId" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OLookupSeq" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OExtendSeq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OAnd" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OImpl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OSeed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ORandom" 'PrefixI 'False) (U1 :: Type -> Type)))))))

opArity :: Op -> Int Source #

Get the arity (desired number of arguments) of a function constant. A few constants have arity 0; everything else is uncurried and hence has arity 1.