Abbie's Haskell compiler
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 
 

33 lines
836 B

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DefaultSignatures #-}
module Frontend.Parser.Posn where
import Frontend.Lexer.Tokens
import Data.Typeable
data Posn
= Posn { posnLine :: {-# UNPACK #-} !Int
, posnColm :: {-# UNPACK #-} !Int
}
deriving (Eq, Show, Ord)
class HasPosn a where
startPosn :: a -> Posn
endPosn :: a -> Posn
span :: (HasPosn b, HasPosn c) => b -> c -> a -> a
default span :: Typeable a => b -> c -> a -> a
span _ _ x = error $ "Can't span " ++ show (typeOf x)
instance HasPosn Token where
startPosn (Token _ l c) = Posn l c
endPosn (Token t l c) = Posn l (c + tokSize t)
instance HasPosn (Posn, Posn, a) where
startPosn (s, _, _) = s
endPosn (_, e, _) = e
span start end (_, _, x) = (startPosn start, endPosn end, x)
thd :: (a, b, c) -> c
thd (_, _, z) = z