sparsec

simple Haskell parser combinator library
git clone git://git.rr3.xyz/sparsec
Log | Files | Refs | README | LICENSE

Loc.hs (1807B)


      1 module Sparsec.Loc (
      2     Loc#,
      3     pattern Loc#,
      4     locByte#,
      5     locRow#,
      6     locCol#,
      7     locEq#,
      8     locShow#,
      9     locAdvance#,
     10     Loc (..),
     11     pattern Loc,
     12     locZero,
     13 ) where
     14 
     15 import GHC.Exts (Int (..), Int#, (+#), (==#))
     16 
     17 intEq# :: Int# -> Int# -> Bool
     18 intEq# x y = case x ==# y of
     19     0# -> False
     20     _ -> True
     21 
     22 newtype Loc# = Loc_# (# Int#, Int#, Int# #)
     23 
     24 pattern Loc# :: Int# -> Int# -> Int# -> Loc#
     25 pattern Loc# b r c = Loc_# (# b, r, c #)
     26 {-# COMPLETE Loc# #-}
     27 
     28 locByte# :: Loc# -> Int#
     29 locByte# (Loc# b _ _) = b
     30 {-# INLINE locByte# #-}
     31 
     32 locRow# :: Loc# -> Int#
     33 locRow# (Loc# _ r _) = r
     34 {-# INLINE locRow# #-}
     35 
     36 locCol# :: Loc# -> Int#
     37 locCol# (Loc# _ _ c) = c
     38 {-# INLINE locCol# #-}
     39 
     40 locEq# :: Loc# -> Loc# -> Bool
     41 locEq# (Loc# b0 r0 c0) (Loc# b1 r1 c1) =
     42     b0 `intEq#` b1 && r0 `intEq#` r1 && c0 `intEq#` c1
     43 {-# INLINE locEq# #-}
     44 
     45 locShow# :: Loc# -> String
     46 locShow# (Loc# b r c) = show (I# b) ++ "@" ++ show (I# r) ++ ":" ++ show (I# c)
     47 {-# INLINE locShow# #-}
     48 
     49 locAdvance# :: Char -> Int -> Loc# -> Loc#
     50 locAdvance# x (I# w) (Loc# b r c) = case x of
     51     '\n' -> Loc# (b +# w) (r +# 1#) 0#
     52     _ -> Loc# (b +# w) r (c +# 1#)
     53 {-# INLINE locAdvance# #-}
     54 
     55 -- | Loc is a source code location, tracking byte offset, row (number of '\n'
     56 -- characters seen so far), and column (number of characters into the current
     57 -- row). All three of these quantities are 0-based. The column tracking is
     58 -- somewhat stupid in that it treats each Unicode codepoint as one column.
     59 data Loc = LocBox {locUnbox :: Loc#}
     60 
     61 pattern Loc :: Int# -> Int# -> Int# -> Loc
     62 pattern Loc b r c = LocBox (Loc# b r c)
     63 {-# COMPLETE Loc #-}
     64 
     65 locZero :: Loc
     66 locZero = Loc 0# 0# 0#
     67 {-# INLINE locZero #-}
     68 
     69 instance Eq Loc where
     70     LocBox l0 == LocBox l1 = l0 `locEq#` l1
     71 
     72 instance Show Loc where
     73     show (LocBox l) = locShow# l