sparsec

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

Span.hs (1187B)


      1 module Sparsec.Span (
      2     Span#,
      3     pattern Span#,
      4     spanBeg#,
      5     spanEnd#,
      6     spanEq#,
      7     spanShow#,
      8     Span (..),
      9     pattern Span,
     10 ) where
     11 
     12 import Sparsec.Loc
     13 
     14 newtype Span# = Span_# (# Loc#, Loc# #)
     15 
     16 pattern Span# :: Loc# -> Loc# -> Span#
     17 pattern Span# beg end = Span_# (# beg, end #)
     18 {-# COMPLETE Span# #-}
     19 
     20 spanBeg# :: Span# -> Loc#
     21 spanBeg# (Span# beg _) = beg
     22 {-# INLINE spanBeg# #-}
     23 
     24 spanEnd# :: Span# -> Loc#
     25 spanEnd# (Span# _ end) = end
     26 {-# INLINE spanEnd# #-}
     27 
     28 spanEq# :: Span# -> Span# -> Bool
     29 spanEq# (Span# beg0 end0) (Span# beg1 end1) =
     30     beg0 `locEq#` beg1 && end0 `locEq#` end1
     31 {-# INLINE spanEq# #-}
     32 
     33 spanShow# :: Span# -> String
     34 spanShow# (Span# beg end) = locShow# beg ++ "--" ++ locShow# end
     35 {-# INLINE spanShow# #-}
     36 
     37 -- | Span is a pair of Loc's specifying a range in the input. The beginning/left
     38 -- Loc is inclusive and the ending/right Loc is exclusive.
     39 data Span = SpanBox {spanUnbox :: Span#}
     40 
     41 pattern Span :: Loc# -> Loc# -> Span
     42 pattern Span beg end = SpanBox (Span# beg end)
     43 {-# COMPLETE Span #-}
     44 
     45 instance Eq Span where
     46     SpanBox span0 == SpanBox span1 = span0 `spanEq#` span1
     47 
     48 instance Show Span where
     49     show (SpanBox span) = spanShow# span