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 (Eq)
posnFilename :: Posn -> FilePath
posnFilename (Pn f _ _ _) = f
posnLine, posnColumn :: Posn -> Int
posnLine   (Pn _ x _ _) = x
posnColumn (Pn _ _ x _) = x
noPos :: Posn
noPos = Pn "no recorded position" 0 0 Nothing
posInNewCxt :: String -> Maybe Posn -> Posn
posInNewCxt name pos = Pn name 1 1 pos
instance Show Posn where
      showsPrec _ (Pn f l c i) = showString "file " .
                                 showString f .
                                 showString "  at line " . shows l .
                                 showString " col " . shows c .
                                 ( case i of
                                    Nothing -> id
                                    Just p  -> showString "\n    used by  " .
                                               shows p )
forcep :: Posn -> Int
forcep (Pn _ n m _) = m `seq` n
addcol :: Int -> Posn -> Posn
addcol n (Pn f r c i) = Pn f r (c+n) i
newline, tab :: Posn -> Posn
newline (Pn f r _ i) = Pn f (r+1) 1 i
tab     (Pn f r c i) = Pn f r (((c`div`8)+1)*8) i
white :: Char -> Posn -> Posn
white ' '    = addcol 1
white '\n'   = newline
white '\r'   = id
white '\t'   = tab
white '\xa0' = addcol 1
white x | isSpace x = addcol 1 
white _      = error "precondition not satisfied: Posn.white c | isSpace c"