curry-base-1.1.1: Functions for manipulating Curry programs

Copyright(c) 1999 - 2004 Wolfgang Lux
2005 Martin Engelke
2011 - 2015 Björn Peemöller
2014 Jan Rasmus Tikovsky
2016 Finn Teegen
LicenseBSD-3-clause
Maintainerbjp@informatik.uni-kiel.de
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Curry.Syntax.Type

Contents

Description

This module provides the necessary data structures to maintain the parsed representation of a Curry program.

Synopsis

Module header

data Module a Source #

Curry module

Instances
Functor Module Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Module a -> Module b #

(<$) :: a -> Module b -> Module a #

Eq a => Eq (Module a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Module a -> Module a -> Bool #

(/=) :: Module a -> Module a -> Bool #

Read a => Read (Module a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Module a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> Module a -> ShowS #

show :: Module a -> String #

showList :: [Module a] -> ShowS #

HasPosition (Module a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (Module a) Source # 
Instance details

Defined in Curry.Syntax.Type

Module pragmas

data Extension Source #

Specified language extensions, either known or unknown.

Constructors

KnownExtension Position KnownExtension

a known extension

UnknownExtension Position String

an unknown extension

data KnownExtension Source #

Known language extensions of Curry.

Constructors

AnonFreeVars

anonymous free variables

CPP

C preprocessor

FunctionalPatterns

functional patterns

NegativeLiterals

negative literals

NoImplicitPrelude

no implicit import of the prelude

data Tool Source #

Different Curry tools which may accept compiler options.

Instances
Eq Tool Source # 
Instance details

Defined in Curry.Syntax.Extension

Methods

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

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

Read Tool Source # 
Instance details

Defined in Curry.Syntax.Extension

Show Tool Source # 
Instance details

Defined in Curry.Syntax.Extension

Methods

showsPrec :: Int -> Tool -> ShowS #

show :: Tool -> String #

showList :: [Tool] -> ShowS #

Export specification

Import declarations

type Qualified = Bool Source #

Flag to signal qualified import

Interface

data Interface Source #

Module interface

Interface declarations are restricted to type declarations and signatures. Note that an interface function declaration additionaly contains the function arity (= number of parameters) in order to generate correct FlatCurry function applications.

type Arity = Int Source #

Arity of a function

data KindExpr Source #

Kind expressions

Instances
Eq KindExpr Source # 
Instance details

Defined in Curry.Syntax.Type

Read KindExpr Source # 
Instance details

Defined in Curry.Syntax.Type

Show KindExpr Source # 
Instance details

Defined in Curry.Syntax.Type

type IMethodImpl = (Ident, Arity) Source #

Class method implementations

Declarations

data Decl a Source #

Declaration in a module

Instances
Functor Decl Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Decl a -> Decl b #

(<$) :: a -> Decl b -> Decl a #

Eq a => Eq (Decl a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Decl a -> Decl a -> Bool #

(/=) :: Decl a -> Decl a -> Bool #

Read a => Read (Decl a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Decl a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> Decl a -> ShowS #

show :: Decl a -> String #

showList :: [Decl a] -> ShowS #

HasPosition (Decl a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (Decl a) Source # 
Instance details

Defined in Curry.Syntax.Type

type Precedence = Integer Source #

Operator precedence

data Infix Source #

Fixity of operators

Constructors

InfixL

left-associative

InfixR

right-associative

Infix

no associativity

Instances
Eq Infix Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

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

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

Read Infix Source # 
Instance details

Defined in Curry.Syntax.Type

Show Infix Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> Infix -> ShowS #

show :: Infix -> String #

showList :: [Infix] -> ShowS #

Pretty Infix Source # 
Instance details

Defined in Curry.Syntax.Type

data Equation a Source #

Function defining equation

Constructors

Equation SpanInfo (Lhs a) (Rhs a) 
Instances
Functor Equation Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Equation a -> Equation b #

(<$) :: a -> Equation b -> Equation a #

Eq a => Eq (Equation a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Equation a -> Equation a -> Bool #

(/=) :: Equation a -> Equation a -> Bool #

Read a => Read (Equation a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Equation a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> Equation a -> ShowS #

show :: Equation a -> String #

showList :: [Equation a] -> ShowS #

HasPosition (Equation a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (Equation a) Source # 
Instance details

Defined in Curry.Syntax.Type

data Lhs a Source #

Left-hand-side of an Equation (function identifier and patterns)

Instances
Functor Lhs Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Lhs a -> Lhs b #

(<$) :: a -> Lhs b -> Lhs a #

Eq a => Eq (Lhs a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Lhs a -> Lhs a -> Bool #

(/=) :: Lhs a -> Lhs a -> Bool #

Read a => Read (Lhs a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Lhs a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> Lhs a -> ShowS #

show :: Lhs a -> String #

showList :: [Lhs a] -> ShowS #

HasPosition (Lhs a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (Lhs a) Source # 
Instance details

Defined in Curry.Syntax.Type

data Rhs a Source #

Right-hand-side of an Equation

Instances
Functor Rhs Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Rhs a -> Rhs b #

(<$) :: a -> Rhs b -> Rhs a #

Eq a => Eq (Rhs a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Rhs a -> Rhs a -> Bool #

(/=) :: Rhs a -> Rhs a -> Bool #

Read a => Read (Rhs a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Rhs a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> Rhs a -> ShowS #

show :: Rhs a -> String #

showList :: [Rhs a] -> ShowS #

HasPosition (Rhs a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (Rhs a) Source # 
Instance details

Defined in Curry.Syntax.Type

data CondExpr a Source #

Conditional expression (expression conditioned by a guard)

Constructors

CondExpr SpanInfo (Expression a) (Expression a) 
Instances
Functor CondExpr Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> CondExpr a -> CondExpr b #

(<$) :: a -> CondExpr b -> CondExpr a #

Eq a => Eq (CondExpr a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: CondExpr a -> CondExpr a -> Bool #

(/=) :: CondExpr a -> CondExpr a -> Bool #

Read a => Read (CondExpr a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (CondExpr a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> CondExpr a -> ShowS #

show :: CondExpr a -> String #

showList :: [CondExpr a] -> ShowS #

HasPosition (CondExpr a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (CondExpr a) Source # 
Instance details

Defined in Curry.Syntax.Type

data Literal Source #

Literal

Instances
Eq Literal Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

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

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

Read Literal Source # 
Instance details

Defined in Curry.Syntax.Type

Show Literal Source # 
Instance details

Defined in Curry.Syntax.Type

data Pattern a Source #

Constructor term (used for patterns)

Instances
Functor Pattern Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Pattern a -> Pattern b #

(<$) :: a -> Pattern b -> Pattern a #

Eq a => Eq (Pattern a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Pattern a -> Pattern a -> Bool #

(/=) :: Pattern a -> Pattern a -> Bool #

Read a => Read (Pattern a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Pattern a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> Pattern a -> ShowS #

show :: Pattern a -> String #

showList :: [Pattern a] -> ShowS #

HasPosition (Pattern a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (Pattern a) Source # 
Instance details

Defined in Curry.Syntax.Type

data Expression a Source #

Expression

Instances
Functor Expression Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Expression a -> Expression b #

(<$) :: a -> Expression b -> Expression a #

Eq a => Eq (Expression a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Expression a -> Expression a -> Bool #

(/=) :: Expression a -> Expression a -> Bool #

Read a => Read (Expression a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Expression a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasPosition (Expression a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (Expression a) Source # 
Instance details

Defined in Curry.Syntax.Type

data InfixOp a Source #

Infix operation

Instances
Functor InfixOp Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> InfixOp a -> InfixOp b #

(<$) :: a -> InfixOp b -> InfixOp a #

Eq a => Eq (InfixOp a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: InfixOp a -> InfixOp a -> Bool #

(/=) :: InfixOp a -> InfixOp a -> Bool #

Read a => Read (InfixOp a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (InfixOp a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> InfixOp a -> ShowS #

show :: InfixOp a -> String #

showList :: [InfixOp a] -> ShowS #

HasPosition (InfixOp a) Source # 
Instance details

Defined in Curry.Syntax.Type

data Statement a Source #

Statement (used for do-sequence and list comprehensions)

Instances
Functor Statement Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Statement a -> Statement b #

(<$) :: a -> Statement b -> Statement a #

Eq a => Eq (Statement a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Statement a -> Statement a -> Bool #

(/=) :: Statement a -> Statement a -> Bool #

Read a => Read (Statement a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Statement a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasPosition (Statement a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (Statement a) Source # 
Instance details

Defined in Curry.Syntax.Type

data CaseType Source #

Type of case expressions

Constructors

Rigid 
Flex 
Instances
Eq CaseType Source # 
Instance details

Defined in Curry.Syntax.Type

Read CaseType Source # 
Instance details

Defined in Curry.Syntax.Type

Show CaseType Source # 
Instance details

Defined in Curry.Syntax.Type

data Alt a Source #

Single case alternative

Constructors

Alt SpanInfo (Pattern a) (Rhs a) 
Instances
Functor Alt Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Alt a -> Alt b #

(<$) :: a -> Alt b -> Alt a #

Eq a => Eq (Alt a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Alt a -> Alt a -> Bool #

(/=) :: Alt a -> Alt a -> Bool #

Read a => Read (Alt a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Alt a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> Alt a -> ShowS #

show :: Alt a -> String #

showList :: [Alt a] -> ShowS #

HasPosition (Alt a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (Alt a) Source # 
Instance details

Defined in Curry.Syntax.Type

data Field a Source #

Record field

Constructors

Field SpanInfo QualIdent a 
Instances
Functor Field Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Field a -> Field b #

(<$) :: a -> Field b -> Field a #

Eq a => Eq (Field a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Field a -> Field a -> Bool #

(/=) :: Field a -> Field a -> Bool #

Read a => Read (Field a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Field a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> Field a -> ShowS #

show :: Field a -> String #

showList :: [Field a] -> ShowS #

HasPosition (Field a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (Field a) Source # 
Instance details

Defined in Curry.Syntax.Type

data Var a Source #

Annotated identifier

Constructors

Var a Ident 
Instances
Functor Var Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Var a -> Var b #

(<$) :: a -> Var b -> Var a #

Eq a => Eq (Var a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Var a -> Var a -> Bool #

(/=) :: Var a -> Var a -> Bool #

Read a => Read (Var a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Var a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> Var a -> ShowS #

show :: Var a -> String #

showList :: [Var a] -> ShowS #

Type classes

Goals

data Goal a Source #

Goal in REPL (expression to evaluate)

Constructors

Goal SpanInfo (Expression a) [Decl a] 
Instances
Functor Goal Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

fmap :: (a -> b) -> Goal a -> Goal b #

(<$) :: a -> Goal b -> Goal a #

Eq a => Eq (Goal a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

(==) :: Goal a -> Goal a -> Bool #

(/=) :: Goal a -> Goal a -> Bool #

Read a => Read (Goal a) Source # 
Instance details

Defined in Curry.Syntax.Type

Show a => Show (Goal a) Source # 
Instance details

Defined in Curry.Syntax.Type

Methods

showsPrec :: Int -> Goal a -> ShowS #

show :: Goal a -> String #

showList :: [Goal a] -> ShowS #

HasPosition (Goal a) Source # 
Instance details

Defined in Curry.Syntax.Type

HasSpanInfo (Goal a) Source # 
Instance details

Defined in Curry.Syntax.Type