module Text.XML.HaXml.Posn
(
Posn()
, posInNewCxt
, noPos
, forcep
, addcol, newline, tab, white
, posnFilename, posnLine, posnColumn
) where
import Data.Char
data Posn = Pn String !Int !Int (Maybe Posn)
deriving (Posn -> Posn -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Posn -> Posn -> Bool
$c/= :: Posn -> Posn -> Bool
== :: Posn -> Posn -> Bool
$c== :: Posn -> Posn -> Bool
Eq)
posnFilename :: Posn -> FilePath
posnFilename :: Posn -> String
posnFilename (Pn String
f Int
_ Int
_ Maybe Posn
_) = String
f
posnLine, posnColumn :: Posn -> Int
posnLine :: Posn -> Int
posnLine (Pn String
_ Int
x Int
_ Maybe Posn
_) = Int
x
posnColumn :: Posn -> Int
posnColumn (Pn String
_ Int
_ Int
x Maybe Posn
_) = Int
x
noPos :: Posn
noPos :: Posn
noPos = String -> Int -> Int -> Maybe Posn -> Posn
Pn String
"no recorded position" Int
0 Int
0 forall a. Maybe a
Nothing
posInNewCxt :: String -> Maybe Posn -> Posn
posInNewCxt :: String -> Maybe Posn -> Posn
posInNewCxt String
name Maybe Posn
pos = String -> Int -> Int -> Maybe Posn -> Posn
Pn String
name Int
1 Int
1 Maybe Posn
pos
instance Show Posn where
showsPrec :: Int -> Posn -> ShowS
showsPrec Int
_ (Pn String
f Int
l Int
c Maybe Posn
i) = String -> ShowS
showString String
"file " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
f forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
" at line " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> ShowS
shows Int
l forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
" col " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> ShowS
shows Int
c forall b c a. (b -> c) -> (a -> b) -> a -> c
.
( case Maybe Posn
i of
Maybe Posn
Nothing -> forall a. a -> a
id
Just Posn
p -> String -> ShowS
showString String
"\n used by " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a. Show a => a -> ShowS
shows Posn
p )
forcep :: Posn -> Int
forcep :: Posn -> Int
forcep (Pn String
_ Int
n Int
m Maybe Posn
_) = Int
m seq :: forall a b. a -> b -> b
`seq` Int
n
addcol :: Int -> Posn -> Posn
addcol :: Int -> Posn -> Posn
addcol Int
n (Pn String
f Int
r Int
c Maybe Posn
i) = String -> Int -> Int -> Maybe Posn -> Posn
Pn String
f Int
r (Int
cforall a. Num a => a -> a -> a
+Int
n) Maybe Posn
i
newline, tab :: Posn -> Posn
newline :: Posn -> Posn
newline (Pn String
f Int
r Int
_ Maybe Posn
i) = String -> Int -> Int -> Maybe Posn -> Posn
Pn String
f (Int
rforall a. Num a => a -> a -> a
+Int
1) Int
1 Maybe Posn
i
tab :: Posn -> Posn
tab (Pn String
f Int
r Int
c Maybe Posn
i) = String -> Int -> Int -> Maybe Posn -> Posn
Pn String
f Int
r (((Int
cforall a. Integral a => a -> a -> a
`div`Int
8)forall a. Num a => a -> a -> a
+Int
1)forall a. Num a => a -> a -> a
*Int
8) Maybe Posn
i
white :: Char -> Posn -> Posn
white :: Char -> Posn -> Posn
white Char
' ' = Int -> Posn -> Posn
addcol Int
1
white Char
'\n' = Posn -> Posn
newline
white Char
'\r' = forall a. a -> a
id
white Char
'\t' = Posn -> Posn
tab
white Char
'\xa0' = Int -> Posn -> Posn
addcol Int
1
white Char
x | Char -> Bool
isSpace Char
x = Int -> Posn -> Posn
addcol Int
1
white Char
_ = forall a. HasCallStack => String -> a
error String
"precondition not satisfied: Posn.white c | isSpace c"