1
1
mirror of https://github.com/github/semantic.git synced 2024-12-24 23:42:31 +03:00

Add a newtype wrapper around Path.

This commit is contained in:
Rob Rix 2019-10-10 13:08:14 -04:00
parent 2be7c29dad
commit d044ea2fc4
No known key found for this signature in database
GPG Key ID: F188A01508EA1CF7
3 changed files with 10 additions and 6 deletions

View File

@ -206,7 +206,7 @@ addressStyle heap = (G.defaultStyle vertex) { G.edgeAttributes }
Unit -> "()"
Bool b -> pack $ show b
String s -> pack $ show s
Closure (Loc p (Span s e)) n _ _ -> "\\\\ " <> unName n <> " [" <> p <> ":" <> showPos s <> "-" <> showPos e <> "]"
Closure (Loc p (Span s e)) n _ _ -> "\\\\ " <> unName n <> " [" <> getPath p <> ":" <> showPos s <> "-" <> showPos e <> "]"
Record _ -> "{}"
showPos (Pos l c) = pack (show l) <> ":" <> pack (show c)

View File

@ -129,9 +129,9 @@ prog5 = fromBody $ ann (do'
prog6 :: (Carrier sig t, Member Core sig) => [File (t Name)]
prog6 =
[ File (Loc "dep" (locSpan (fromJust here))) $ Core.record
[ File (Loc (Path "dep") (locSpan (fromJust here))) $ Core.record
[ ("dep", Core.record [ ("var", Core.bool True) ]) ]
, File (Loc "main" (locSpan (fromJust here))) $ do' (map (Nothing :<-)
, File (Loc (Path "main") (locSpan (fromJust here))) $ do' (map (Nothing :<-)
[ load (Core.string "dep")
, Core.record [ ("thing", pure "dep" Core.... "var") ]
])

View File

@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
module Data.Loc
( Loc(..)
, Path(..)
, interactive
, here
, stackLoc
@ -10,14 +11,17 @@ import Data.Text (Text, pack)
import GHC.Stack
import Source.Span
newtype Path = Path { getPath :: Text }
deriving (Eq, Ord, Show)
data Loc = Loc
{ locPath :: !Text
{ locPath :: !Path
, locSpan :: {-# UNPACK #-} !Span
}
deriving (Eq, Ord, Show)
interactive :: Loc
interactive = Loc "<interactive>" (Span (Pos 1 1) (Pos 1 1))
interactive = Loc (Path "<interactive>") (Span (Pos 1 1) (Pos 1 1))
here :: HasCallStack => Maybe Loc
@ -29,4 +33,4 @@ stackLoc cs = case getCallStack cs of
_ -> Nothing
fromGHCSrcLoc :: SrcLoc -> Loc
fromGHCSrcLoc SrcLoc{..} = Loc (pack srcLocFile) (Span (Pos srcLocStartLine srcLocStartCol) (Pos srcLocEndLine srcLocEndCol))
fromGHCSrcLoc SrcLoc{..} = Loc (Path (pack srcLocFile)) (Span (Pos srcLocStartLine srcLocStartCol) (Pos srcLocEndLine srcLocEndCol))