{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE Trustworthy #-}
module Grisette.Core.Data.FileLocation
(
FileLocation (..),
nameWithLoc,
slocsym,
ilocsym,
)
where
import Control.DeepSeq
import Data.Hashable
import Debug.Trace.LocationTH (__LOCATION__)
import GHC.Generics
import Grisette.Core.Data.Class.GenSym
import Grisette.Core.Data.Class.Solvable
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Syntax.Compat
data FileLocation = FileLocation {FileLocation -> String
locPath :: String, FileLocation -> Int
locLineno :: Int, FileLocation -> (Int, Int)
locSpan :: (Int, Int)}
deriving (FileLocation -> FileLocation -> Bool
(FileLocation -> FileLocation -> Bool)
-> (FileLocation -> FileLocation -> Bool) -> Eq FileLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileLocation -> FileLocation -> Bool
$c/= :: FileLocation -> FileLocation -> Bool
== :: FileLocation -> FileLocation -> Bool
$c== :: FileLocation -> FileLocation -> Bool
Eq, Eq FileLocation
Eq FileLocation
-> (FileLocation -> FileLocation -> Ordering)
-> (FileLocation -> FileLocation -> Bool)
-> (FileLocation -> FileLocation -> Bool)
-> (FileLocation -> FileLocation -> Bool)
-> (FileLocation -> FileLocation -> Bool)
-> (FileLocation -> FileLocation -> FileLocation)
-> (FileLocation -> FileLocation -> FileLocation)
-> Ord FileLocation
FileLocation -> FileLocation -> Bool
FileLocation -> FileLocation -> Ordering
FileLocation -> FileLocation -> FileLocation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FileLocation -> FileLocation -> FileLocation
$cmin :: FileLocation -> FileLocation -> FileLocation
max :: FileLocation -> FileLocation -> FileLocation
$cmax :: FileLocation -> FileLocation -> FileLocation
>= :: FileLocation -> FileLocation -> Bool
$c>= :: FileLocation -> FileLocation -> Bool
> :: FileLocation -> FileLocation -> Bool
$c> :: FileLocation -> FileLocation -> Bool
<= :: FileLocation -> FileLocation -> Bool
$c<= :: FileLocation -> FileLocation -> Bool
< :: FileLocation -> FileLocation -> Bool
$c< :: FileLocation -> FileLocation -> Bool
compare :: FileLocation -> FileLocation -> Ordering
$ccompare :: FileLocation -> FileLocation -> Ordering
Ord, (forall x. FileLocation -> Rep FileLocation x)
-> (forall x. Rep FileLocation x -> FileLocation)
-> Generic FileLocation
forall x. Rep FileLocation x -> FileLocation
forall x. FileLocation -> Rep FileLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FileLocation x -> FileLocation
$cfrom :: forall x. FileLocation -> Rep FileLocation x
Generic, (forall (m :: * -> *). Quote m => FileLocation -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
FileLocation -> Code m FileLocation)
-> Lift FileLocation
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => FileLocation -> m Exp
forall (m :: * -> *).
Quote m =>
FileLocation -> Code m FileLocation
liftTyped :: forall (m :: * -> *).
Quote m =>
FileLocation -> Code m FileLocation
$cliftTyped :: forall (m :: * -> *).
Quote m =>
FileLocation -> Code m FileLocation
lift :: forall (m :: * -> *). Quote m => FileLocation -> m Exp
$clift :: forall (m :: * -> *). Quote m => FileLocation -> m Exp
Lift, FileLocation -> ()
(FileLocation -> ()) -> NFData FileLocation
forall a. (a -> ()) -> NFData a
rnf :: FileLocation -> ()
$crnf :: FileLocation -> ()
NFData, Int -> FileLocation -> Int
FileLocation -> Int
(Int -> FileLocation -> Int)
-> (FileLocation -> Int) -> Hashable FileLocation
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: FileLocation -> Int
$chash :: FileLocation -> Int
hashWithSalt :: Int -> FileLocation -> Int
$chashWithSalt :: Int -> FileLocation -> Int
Hashable)
instance Show FileLocation where
show :: FileLocation -> String
show (FileLocation String
p Int
l (Int
s1, Int
s2)) = String
p String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
l String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
s1 String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
s2
parseFileLocation :: String -> FileLocation
parseFileLocation :: String -> FileLocation
parseFileLocation String
str =
let r :: String
r = ShowS
forall a. [a] -> [a]
reverse String
str
(String
s2, String
r1) = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-') String
r
(String
s1, String
r2) = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. [a] -> [a]
tail String
r1
(String
l, String
p) = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. [a] -> [a]
tail String
r2
in String -> Int -> (Int, Int) -> FileLocation
FileLocation (ShowS
forall a. [a] -> [a]
reverse ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. [a] -> [a]
tail String
p) (String -> Int
forall a. Read a => String -> a
read (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. [a] -> [a]
reverse String
l) (String -> Int
forall a. Read a => String -> a
read (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. [a] -> [a]
reverse String
s1, String -> Int
forall a. Read a => String -> a
read (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. [a] -> [a]
reverse String
s2)
nameWithLoc :: String -> SpliceQ FreshIdent
nameWithLoc :: String -> SpliceQ FreshIdent
nameWithLoc String
s = [||nameWithInfo s (parseFileLocation $$(liftSplice $ unsafeTExpCoerce __LOCATION__))||]
slocsym :: (Solvable c s) => String -> SpliceQ s
slocsym :: forall c s. Solvable c s => String -> SpliceQ s
slocsym String
nm = [||sinfosym nm (parseFileLocation $$(liftSplice $ unsafeTExpCoerce __LOCATION__))||]
ilocsym :: (Solvable c s) => String -> Int -> SpliceQ s
ilocsym :: forall c s. Solvable c s => String -> Int -> SpliceQ s
ilocsym String
nm Int
idx = [||iinfosym nm idx (parseFileLocation $$(liftSplice $ unsafeTExpCoerce __LOCATION__))||]