module Language.Preprocessor.Cpphs.Position
( Posn(..)
, newfile
, addcol, newline, tab, newlines, newpos
, cppline, haskline, cpp2hask
, filename, lineno, directory
, cleanPath
) where
import Data.List (isPrefixOf)
data Posn = Pn String !Int !Int (Maybe Posn)
deriving (Eq)
instance Show Posn where
showsPrec _ (Pn f l c i) = showString f .
showString " at line " . shows l .
showString " col " . shows c .
( case i of
Nothing -> id
Just p -> showString "\n used by " .
shows p )
newfile :: String -> Posn
newfile name = Pn (cleanPath name) 1 1 Nothing
addcol :: Int -> Posn -> Posn
addcol n (Pn f r c i) = Pn f r (c+n) i
newline :: Posn -> Posn
newline (Pn f r _ i) = let r' = r+1 in r' `seq` Pn f r' 1 i
tab :: Posn -> Posn
tab (Pn f r c i) = Pn f r (((c`div`8)+1)*8) i
newlines :: Int -> Posn -> Posn
newlines n (Pn f r _ i) = Pn f (r+n) 1 i
newpos :: Int -> Maybe String -> Posn -> Posn
newpos r Nothing (Pn f _ c i) = Pn f r c i
newpos r (Just ('"':f)) (Pn _ _ c i) = Pn (init f) r c i
newpos r (Just f) (Pn _ _ c i) = Pn f r c i
lineno :: Posn -> Int
filename :: Posn -> String
directory :: Posn -> FilePath
lineno (Pn _ r _ _) = r
filename (Pn f _ _ _) = f
directory (Pn f _ _ _) = dirname f
cppline :: Posn -> String
cppline (Pn f r _ _) = "#line "++show r++" "++show f
haskline :: Posn -> String
haskline (Pn f r _ _) = "{-# LINE "++show r++" "++show f++" #-}"
cpp2hask :: String -> String
cpp2hask line | "#line" `isPrefixOf` line = "{-# LINE "
++unwords (tail (words line))
++" #-}"
| otherwise = line
dirname :: String -> String
dirname = reverse . safetail . dropWhile (not.(`elem`"\\/")) . reverse
where safetail [] = []
safetail (_:x) = x
cleanPath :: FilePath -> FilePath
cleanPath [] = []
cleanPath ('\\':cs) = '/': cleanPath cs
cleanPath (c:cs) = c: cleanPath cs