{-# LANGUAGE CPP #-}
module SourceMap.Types where
import Data.Int
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid ((<>))
#endif
import Data.Text
import Data.Function
data SourceMapping = SourceMapping
{ SourceMapping -> FilePath
smFile :: !FilePath
, SourceMapping -> Maybe FilePath
smSourceRoot :: !(Maybe FilePath)
, SourceMapping -> [Mapping]
smMappings :: ![Mapping]
} deriving Int -> SourceMapping -> ShowS
[SourceMapping] -> ShowS
SourceMapping -> FilePath
(Int -> SourceMapping -> ShowS)
-> (SourceMapping -> FilePath)
-> ([SourceMapping] -> ShowS)
-> Show SourceMapping
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [SourceMapping] -> ShowS
$cshowList :: [SourceMapping] -> ShowS
show :: SourceMapping -> FilePath
$cshow :: SourceMapping -> FilePath
showsPrec :: Int -> SourceMapping -> ShowS
$cshowsPrec :: Int -> SourceMapping -> ShowS
Show
data Mapping = Mapping
{ Mapping -> Pos
mapGenerated :: !Pos
, Mapping -> Maybe Pos
mapOriginal :: !(Maybe Pos)
, Mapping -> Maybe FilePath
mapSourceFile :: !(Maybe FilePath)
, Mapping -> Maybe Text
mapName :: !(Maybe Text)
} deriving Int -> Mapping -> ShowS
[Mapping] -> ShowS
Mapping -> FilePath
(Int -> Mapping -> ShowS)
-> (Mapping -> FilePath) -> ([Mapping] -> ShowS) -> Show Mapping
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Mapping] -> ShowS
$cshowList :: [Mapping] -> ShowS
show :: Mapping -> FilePath
$cshow :: Mapping -> FilePath
showsPrec :: Int -> Mapping -> ShowS
$cshowsPrec :: Int -> Mapping -> ShowS
Show
data Pos = Pos
{ Pos -> Int32
posLine :: !Int32
, Pos -> Int32
posColumn :: !Int32
} deriving (Pos -> Pos -> Bool
(Pos -> Pos -> Bool) -> (Pos -> Pos -> Bool) -> Eq Pos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pos -> Pos -> Bool
$c/= :: Pos -> Pos -> Bool
== :: Pos -> Pos -> Bool
$c== :: Pos -> Pos -> Bool
Eq,Int -> Pos -> ShowS
[Pos] -> ShowS
Pos -> FilePath
(Int -> Pos -> ShowS)
-> (Pos -> FilePath) -> ([Pos] -> ShowS) -> Show Pos
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Pos] -> ShowS
$cshowList :: [Pos] -> ShowS
show :: Pos -> FilePath
$cshow :: Pos -> FilePath
showsPrec :: Int -> Pos -> ShowS
$cshowsPrec :: Int -> Pos -> ShowS
Show)
instance Ord Pos where
compare :: Pos -> Pos -> Ordering
compare Pos
a Pos
b =
(Int32 -> Int32 -> Ordering)
-> (Pos -> Int32) -> Pos -> Pos -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Int32 -> Int32 -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Pos -> Int32
posLine Pos
a Pos
b Ordering -> Ordering -> Ordering
forall a. Semigroup a => a -> a -> a
<> (Int32 -> Int32 -> Ordering)
-> (Pos -> Int32) -> Pos -> Pos -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Int32 -> Int32 -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Pos -> Int32
posColumn Pos
a Pos
b