Token.hs 3.13 KB
Newer Older
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23
-- Copyright (c) 2013, Kenton Varda <temporal@gmail.com>
-- All rights reserved.
--
-- Redistribution and use in source and binary forms, with or without
-- modification, are permitted provided that the following conditions are met:
--
-- 1. Redistributions of source code must retain the above copyright notice, this
--    list of conditions and the following disclaimer.
-- 2. Redistributions in binary form must reproduce the above copyright notice,
--    this list of conditions and the following disclaimer in the documentation
--    and/or other materials provided with the distribution.
--
-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND
-- ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
-- DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR
-- ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
-- (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
-- LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND
-- ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
-- SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.

24 25
{-# LANGUAGE DeriveDataTypeable #-}

26 27
module Token where

28
import Data.Generics
29 30 31
import Text.Parsec.Pos (SourcePos, sourceLine, sourceColumn)
import Text.Printf (printf)

32
data Located t = Located { locatedPos :: SourcePos, locatedValue :: t } deriving (Typeable, Data)
33 34 35 36

instance Show t => Show (Located t) where
    show (Located pos x) = printf "%d:%d:%s" (sourceLine pos) (sourceColumn pos) (show x)

Kenton Varda's avatar
Kenton Varda committed
37 38 39 40 41 42
instance Eq a => Eq (Located a) where
    Located _ a == Located _ b = a == b

instance Ord a => Ord (Located a) where
    compare (Located _ a) (Located _ b) = compare a b

43
data TokenSequence = TokenSequence [Located Token] SourcePos deriving(Data, Typeable, Show, Eq)
44

45
data Token = Identifier String
46
           | TypeIdentifier String
47 48
           | ParenthesizedList [TokenSequence]
           | BracketedList [TokenSequence]
49 50 51
           | LiteralInt Integer
           | LiteralFloat Double
           | LiteralString String
52
           | VoidKeyword
53 54
           | TrueKeyword
           | FalseKeyword
55 56
           | AtSign
           | Colon
Kenton Varda's avatar
Kenton Varda committed
57
           | DollarSign
58 59
           | Period
           | EqualsSign
Kenton Varda's avatar
Kenton Varda committed
60
           | MinusSign
Kenton Varda's avatar
Kenton Varda committed
61
           | Asterisk
Kenton Varda's avatar
Kenton Varda committed
62
           | ExclamationPoint
Kenton Varda's avatar
Kenton Varda committed
63
           | InKeyword
Kenton Varda's avatar
Kenton Varda committed
64 65
           | OfKeyword    -- We reserve some common, short English words for use as future keywords.
           | OnKeyword
Kenton Varda's avatar
Kenton Varda committed
66 67 68
           | AsKeyword
           | WithKeyword
           | FromKeyword
69
           | ImportKeyword
70
           | UsingKeyword
71 72
           | ConstKeyword
           | EnumKeyword
Kenton Varda's avatar
Kenton Varda committed
73
           | StructKeyword
Kenton Varda's avatar
Kenton Varda committed
74
           | UnionKeyword
75
           | InterfaceKeyword
Kenton Varda's avatar
Kenton Varda committed
76
           | AnnotationKeyword
Kenton Varda's avatar
Kenton Varda committed
77
           | FixedKeyword
78
           deriving (Data, Typeable, Show, Eq)
79

80 81
data Statement = Line TokenSequence
               | Block TokenSequence [Located Statement]
82
               deriving (Show)