1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
{- |
    Module      :  AST
    Description :  Abstract Syntax Tree

    This module contains the description of the curry abstract syntax tree (AST)
    and useful functions on the elements of the AST.
-}






module AST.AST where

import Char (isAlphaNum)
import List (intercalate)

import AST.Span (Pos)

-- ---------------------------------------------------------------------------
-- Types
-- ---------------------------------------------------------------------------

-- |Simple identifier
data Ident = Ident
  { idPosition :: Pos      -- ^ Source code 'Position'
  , idName     :: String   -- ^ Name of the identifier
  , idUnique   :: Int      -- ^ Unique number of the identifier
  }
 deriving Show

-- |Qualified identifier
data QualIdent = QualIdent
  { qidModule :: Maybe ModuleIdent -- ^ optional module identifier
  , qidIdent  :: Ident             -- ^ identifier itself
  }
 deriving Show

-- | Module identifier
data ModuleIdent = ModuleIdent
  { midPosition   :: Pos      -- ^ source code 'Position'
  , midQualifiers :: [String] -- ^ hierarchical idenfiers
  }
 deriving Show

-- |Specified language extensions, either known or unknown.
data Extension
  = KnownExtension   Pos KnownExtension -- ^ a known extension
  | UnknownExtension Pos String         -- ^ an unknown extension
 deriving Show

data KnownExtension
  = AnonFreeVars              -- ^ anonymous free variables
  | FunctionalPatterns        -- ^ functional patterns
  | NegativeLiterals          -- ^ negative literals
  | NoImplicitPrelude         -- ^ no implicit import of the prelude
  | ExistentialQuantification -- ^ existential quantification
 deriving Show

-- |Different Curry tools which may accept compiler options.
data Tool = KICS2 | PAKCS | CYMAKE | UnknownTool String
 deriving Show


-- ---------------------------------------------------------------------------
-- Functions
-- ---------------------------------------------------------------------------

-- |Hierarchical module name
moduleName :: ModuleIdent -> String
moduleName = intercalate "." . midQualifiers

-- |Hierarchical name of qualified Ident
qidName :: QualIdent -> String
qidName q = case q of
  (QualIdent Nothing  i) -> idName i
  (QualIdent (Just m) i) -> intercalate "." [(moduleName m), (idName i)]

-- |Set position of ModuleIdent
setMIdPos :: Pos -> ModuleIdent -> ModuleIdent
setMIdPos p m = m { midPosition = p }

-- |Set position of Ident
setIdPos :: Pos -> Ident -> Ident
setIdPos p i = i { idPosition = p }

-- |Set position of QualIdent
setQIdPos :: Pos -> QualIdent -> QualIdent
setQIdPos p q = q { qidIdent = setIdPos p (qidIdent q) }

-- |Check whether an 'Ident' identifies an infix operation
isInfixOp :: Ident -> Bool
isInfixOp (Ident _ s _) = all (`elem` "~!@#$%^&*+-=<>:?./|\\") s


-- ---------------------------------------------------------------------------
-- Definition of AST: Module
-- ---------------------------------------------------------------------------

-- |Curry module
data Module = Module [ModulePragma] ModuleIdent (Maybe ExportSpec)
                     [ImportDecl] [Decl]
 deriving Show

-- |Module pragma
data ModulePragma
  = LanguagePragma Pos [Extension]
  | OptionsPragma  Pos (Maybe Tool) String
 deriving Show

-- |Export specification
data ExportSpec = Exporting Pos [Export]
 deriving Show

-- |Single exported entity
data Export
  = Export         QualIdent
  | ExportTypeWith QualIdent [Ident]
  | ExportTypeAll  QualIdent
  | ExportModule   ModuleIdent
 deriving Show

-- |Import declaration
data ImportDecl = ImportDecl Pos ModuleIdent Qualified
                             (Maybe ModuleIdent) (Maybe ImportSpec)
 deriving Show

-- |Flag to signal qualified import
type Qualified = Bool

-- |Import specification
data ImportSpec
  = Importing Pos [Import]
  | Hiding    Pos [Import]
 deriving Show

-- |Single imported entity
data Import
  = Import         Ident
  | ImportTypeWith Ident [Ident]
  | ImportTypeAll  Ident
 deriving Show

-- ---------------------------------------------------------------------------
-- Declarations (local or top-level)
-- ---------------------------------------------------------------------------

-- |Declaration in a module
data Decl
  = InfixDecl    Pos Infix (Maybe Precedence) [Ident]
  | DataDecl     Pos Ident [Ident] [ConstrDecl] [QualIdent]
  | NewtypeDecl  Pos Ident [Ident] NewConstrDecl [QualIdent]
  | TypeDecl     Pos Ident [Ident] TypeExpr
  | TypeSig      Pos [Ident] QualTypeExpr
  | FunctionDecl Pos Ident [Equation]
  | ForeignDecl  Pos CallConv (Maybe String) Ident TypeExpr
  | ExternalDecl Pos [Ident]
  | PatternDecl  Pos Pattern Rhs
  | FreeDecl     Pos [Ident]
  | DefaultDecl  Pos [TypeExpr]
  | ClassDecl    Pos Context Ident Ident [Decl]
  | InstanceDecl Pos Context QualIdent InstanceType [Decl]
 deriving Show

-- ---------------------------------------------------------------------------
-- Infix declaration
-- ---------------------------------------------------------------------------

-- |Operator precedence
type Precedence = Int

-- |Fixity of operators
data Infix
  = InfixL -- ^ left-associative
  | InfixR -- ^ right-associative
  | Infix  -- ^ no associativity
 deriving Show

-- |Constructor declaration for algebraic data types
data ConstrDecl
  = ConstrDecl Pos [Ident] Context Ident [TypeExpr]
  | ConOpDecl  Pos [Ident] Context TypeExpr Ident TypeExpr
  | RecordDecl Pos [Ident] Context Ident [FieldDecl]
 deriving Show

-- |Constructor declaration for renaming types (newtypes)
data NewConstrDecl
  = NewConstrDecl Pos Ident TypeExpr
  | NewRecordDecl Pos Ident (Ident, TypeExpr)
 deriving Show

-- |Declaration for labelled fields
data FieldDecl = FieldDecl Pos [Ident] TypeExpr
 deriving Show

-- |Calling convention for C code
data CallConv
  = CallConvPrimitive
  | CallConvCCall
 deriving Show

-- |Type expressions
data TypeExpr
  = ConstructorType QualIdent
  | ApplyType       TypeExpr TypeExpr
  | VariableType    Ident
  | TupleType       [TypeExpr]
  | ListType        TypeExpr
  | ArrowType       TypeExpr TypeExpr
  | ParenType       TypeExpr
 deriving Show

-- |Qualified type expressions
data QualTypeExpr = QualTypeExpr Context TypeExpr
 deriving Show

-- ---------------------------------------------------------------------------
-- Type classes
-- ---------------------------------------------------------------------------

type Context = [Constraint]

data Constraint = Constraint QualIdent TypeExpr
 deriving Show

type InstanceType = TypeExpr

-- ---------------------------------------------------------------------------
-- Functions
-- ---------------------------------------------------------------------------

-- |Equation
data Equation = Equation Pos Lhs Rhs
 deriving Show

-- |Left-hand-side of an `Equation` (function identifier and patterns)
data Lhs
  = FunLhs Ident [Pattern]
  | OpLhs  Pattern Ident Pattern
  | ApLhs  Lhs [Pattern]
 deriving Show

-- |Right-hand-side of an `Equation`
data Rhs
  = SimpleRhs  Pos Expression [Decl]
  | GuardedRhs [CondExpr] [Decl]
 deriving Show

-- |Conditional expression (expression conditioned by a guard)
data CondExpr = CondExpr Pos Expression Expression
 deriving Show

-- |Literal
data Literal
  = Char   Char
  | Int    Int
  | Float  Float
  | String String
 deriving Show

-- |Constructor term (used for patterns)
data Pattern
  = LiteralPattern     Literal
  | NegativePattern    Literal
  | VariablePattern    Ident
  | ConstructorPattern QualIdent [Pattern]
  | InfixPattern       Pattern QualIdent Pattern
  | ParenPattern       Pattern
  | RecordPattern      QualIdent [Field Pattern]
  | TuplePattern       [Pattern]
  | ListPattern        [Pattern]
  | AsPattern          Ident Pattern
  | LazyPattern        Pattern
  | FunctionPattern    QualIdent [Pattern]
  | InfixFuncPattern   Pattern QualIdent Pattern
 deriving Show

-- |Expression
data Expression
  = Literal           Literal
  | Variable          QualIdent
  | Constructor       QualIdent
  | Paren             Expression
  | Typed             Expression QualTypeExpr
  | Record            QualIdent [Field Expression]
  | RecordUpdate      Expression [Field Expression]
  | Tuple             [Expression]
  | List              [Expression]
  | ListCompr         Expression [Statement]
  | EnumFrom          Expression
  | EnumFromThen      Expression Expression
  | EnumFromTo        Expression Expression
  | EnumFromThenTo    Expression Expression Expression
  | UnaryMinus        Expression
  | Apply             Expression Expression
  | InfixApply        Expression InfixOp Expression
  | LeftSection       Expression InfixOp
  | RightSection      InfixOp Expression
  | Lambda            [Pattern] Expression
  | Let               [Decl] Expression
  | Do                [Statement] Expression
  | IfThenElse        Expression Expression Expression
  | Case              CaseType Expression [Alt]
 deriving Show

-- |Infix operation
data InfixOp
  = InfixOp     QualIdent
  | InfixConstr QualIdent
 deriving Show

-- |Statement (used for do-sequence and list comprehensions)
data Statement
  = StmtExpr Expression
  | StmtDecl [Decl]
  | StmtBind Pattern Expression
 deriving Show

-- |Type of case expressions
data CaseType
  = Rigid
  | Flex
 deriving Show

-- |Single case alternative
data Alt = Alt Pos Pattern Rhs
 deriving Show

-- |Record field
data Field a = Field Pos QualIdent a
 deriving Show