module Text.Parsnip.Location
( location
, Location(..)
, located
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as B
import Data.Maybe
data Location = Location
{ Location -> Int
locationLine :: Int
, Location -> Int
locationColumn :: Int
, Location -> ByteString
locationSource :: ByteString
} deriving Int -> Location -> ShowS
[Location] -> ShowS
Location -> String
(Int -> Location -> ShowS)
-> (Location -> String) -> ([Location] -> ShowS) -> Show Location
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Location] -> ShowS
$cshowList :: [Location] -> ShowS
show :: Location -> String
$cshow :: Location -> String
showsPrec :: Int -> Location -> ShowS
$cshowsPrec :: Int -> Location -> ShowS
Show
location :: ByteString -> Int -> Location
location :: ByteString -> Int -> Location
location ByteString
bs Int
j = Int -> Int -> ByteString -> Location
Location (Char -> ByteString -> Int
B.count Char
'\n' ByteString
before) (Int
j Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
k) (ByteString -> Location) -> ByteString -> Location
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> ByteString -> ByteString
B.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'\n') (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
B.drop Int
k ByteString
bs where
before :: ByteString
before = Int -> ByteString -> ByteString
B.take Int
j ByteString
bs
k :: Int
k = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ Char -> ByteString -> Maybe Int
B.elemIndexEnd Char
'\n' ByteString
before
{-# inline location #-}
located :: Location -> String -> String
located :: Location -> ShowS
located (Location Int
l Int
c ByteString
bs) String
msg = [String] -> String
Prelude.unlines
[ 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
c String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg
, String
ls
, 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]
++ ByteString -> String
B.unpack ByteString
bs
, String
ls String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> Char -> String
forall a. Int -> a -> [a]
Prelude.replicate Int
c Char
' ' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"^"
] where ls :: String
ls = Int -> Char -> String
forall a. Int -> a -> [a]
Prelude.replicate (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Int -> String
forall a. Show a => a -> String
show Int
l) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char
' ' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"|"