elm/compiler/SourceSyntax/Location.hs
Evan Czaplicki 5c68f6bb73 Convert more files to the new Expression format that relies more on
patterns. Seems to clean things up so far.

Also, begin adding a module that resorts definitions to make sure
that each definition comes after the ones it depends on. This will
also make it possible to disallow recursive values statically.
2013-07-04 17:24:04 +02:00

44 lines
No EOL
1.1 KiB
Haskell

{-# LANGUAGE DeriveDataTypeable #-}
module SourceSyntax.Location where
import Text.Parsec.Pos
import Data.Data
data SrcPos = Pos Int Int
deriving (Eq, Ord, Data, Typeable)
data SrcSpan = Span SrcPos SrcPos | NoSpan
deriving (Eq, Ord, Data, Typeable)
data Located e = L (Maybe String) SrcSpan e
deriving (Eq, Ord, Data, Typeable)
instance Show SrcPos where
show (Pos r c) = "Line " ++ show r ++ ", Column " ++ show c
instance Show SrcSpan where
show span =
case span of
Span start end -> show start
NoSpan -> ""
instance Show e => Show (Located e) where
show (L _ _ e) = show e
none = L Nothing NoSpan
at start end = L Nothing
(Span (Pos (sourceLine start) (sourceColumn start))
(Pos (sourceLine end ) (sourceColumn end )))
merge (L _ s1 _) (L _ s2 _) = L Nothing span
where span = case (s1,s2) of
(Span start _, Span _ end) -> Span start end
(_, NoSpan) -> s1
(NoSpan, _) -> s2
add x (L Nothing span e) = L (Just (show x)) span e
add x (L txt span e) = L txt span e