Copyright : (c) Klaus L�ttich and Christian Maeder and Uni Bremen 2002-2003
Maintainer : maeder@tzi.de
This module supplies positions, simple and mixfix identifiers.
A simple identifier is a lexical token given by a string and a start position.
- A 'place' is a special token within mixfix identifiers.
- A mixfix identifier may have a compound list.
This compound list follows the last non-place token!
- Identifiers fixed for all logics
data Pos = SourcePos { sourceName :: String
comparePos :: Pos -> Pos -> Ordering
comparePos (SourcePos s1 l1 c1) (SourcePos s2 l2 c2) =
compare (s1, l1, c1) (s2, l2, c2)
-- | construct a new position
newPos :: String -> Int -> Int -> Pos
-- | increment the column counter
incSourceColumn :: Pos -> Int -> Pos
incSourceColumn (SourcePos s l c) i = SourcePos s l (c + i)
showPos p = let name = sourceName p
in noShow (null name) (showString name . showChar ':') .
noShow (line == 0 && column == 0)
(shows line . showChar '.' . shows column)
-- * Tokens as 'String's with positions that are ignored for 'Eq' and 'Ord'
-- | tokens as supplied by the scanner
data Token = Token { tokStr :: String
instance Show Token where
-- | simple ids are just tokens
-- | a 'Token' with 'nullPos'
mkSimpleId :: String -> Token
mkSimpleId s = Token s []
extSimpleId :: String -> SIMPLE_ID -> SIMPLE_ID
extSimpleId s sid = sid {tokStr = tokStr sid ++ s}
-- | show the plain string
showTok :: Token -> ShowS
showTok = showString . tokStr
Token s1 _ == Token s2 _ = s1 == s2
Token s1 _ <= Token s2 _ = s1 <= s2
catPos :: [Token] -> [Pos]
catPos = concatMap tokPos
-- | shortcut to get positions of surrounding and interspersed tokens
toPos :: Token -> [Token] -> Token -> [Pos]
toPos o l c = catPos $ o:l++[c]
isPlace (Token t _) = t == place
-- * identifiers with positions (usually ignored) of compound lists
-- | mixfix and compound identifiers
data Id = Id [Token] [Id] [Pos]
-- pos of square brackets and commas of a compound list
-- | construct an 'Id' from a token list
mkId toks = Id toks [] []
Id tops1 ids1 _ == Id tops2 ids2 _ = (tops1, ids1) == (tops2, ids2)
Id tops1 ids1 _ <= Id tops2 ids2 _ = (tops1, ids1) <= (tops2, ids2)
-- | shortcut to suppress output for input condition
noShow :: Bool -> ShowS -> ShowS
noShow b s = if b then id else s
-- | intersperse seperators
showSepList :: ShowS -> (a -> ShowS) -> [a] -> ShowS
showSepList _ f [x] = f x
showSepList s f (x:r) = f x . s . showSepList s f r
-- | shows a compound list
showIds is = noShow (null is) $ showString "["
. showSepList (showString ",") showId is
-- | shows an 'Id', puts final places behind a compound list
let (toks, places) = splitMixToken ts
showToks = showSepList id showTok
in showToks toks . showIds is . showToks places
-- ** splitting identifiers
-- | splits off the front and final places
splitMixToken :: [Token] -> ([Token],[Token])
splitMixToken [] = ([], [])
let (toks, pls) = splitMixToken l
in if isPlace h && null toks
-- | return open and closing list bracket and a compound list
getListBrackets :: Id -> ([Token], [Token], [Id])
getListBrackets (Id b cs _) =
let (b1, rest) = break isPlace b
b2 = if null rest then []
else filter (not . isPlace) rest
-- ** reconstructing token lists
-- | reconstruct a list with surrounding strings and interspersed commas
-- with proper position information
-- that should be preserved by the input function
expandPos :: (Token -> a) -> (String, String) -> [a] -> [Pos] -> [a]
-- expandPos f ("{", "}") [a,b] [(1,1), (1,3), 1,5)] =
-- [ t"{" , a , t"," , b , t"}" ] where t = f . Token (and proper positions)
expandPos f (o, c) ts ps =
if null ts then if null ps then map (f . mkSimpleId) [o, c]
else map f (zipWith Token [o, c] [[head ps] , [last ps]])
else let n = length ts + 1
commas j = if j == 2 then [c] else "," : commas (j - 1)
seps = map f (if diff == 0 then
zipWith ( \ s p -> Token s [p])
ocs ps else map mkSimpleId ocs)
in head seps : concat (zipWith (\ t s -> [t,s]) ts (tail seps))
-- | reconstruct the token list of an 'Id'
-- including square brackets and commas of (nested) compound lists.
getPlainTokenList :: Id -> [Token]
getPlainTokenList (Id ts cs ps) =
let (toks, pls) = splitMixToken ts in
toks ++ getCompoundTokenList cs ps ++ pls
-- | reconstruct tokens of compound list
getCompoundTokenList :: [Id] -> [Pos] -> [Token]
getCompoundTokenList cs ps = concat $ expandPos (:[]) ("[", "]")
-- although positions will be replaced (by scan)
(map getPlainTokenList cs) ps
-- ** conversion from 'SIMPLE_ID'
-- | a 'SIMPLE_ID' as 'Id'
simpleIdToId :: SIMPLE_ID -> Id
simpleIdToId sid = Id [sid] [] []
-- | efficiently test for a singleton list
-- | test for a 'SIMPLE_ID'
isSimpleId (Id ts cs _) = null cs && isSingle ts
-- | number of 'place' in 'Id'
placeCount (Id tops _ _) = length $ filter isPlace tops
-- | has no (toplevel) 'place'
isOrdAppl = not . isMixfix
isMixfix (Id tops _ _) = any isPlace tops
isPrefix (Id tops _ _) = not (null tops) && not (isPlace (head tops))
-- | starts with a 'place'
isPostfix (Id tops _ _) = not (null tops) && isPlace (head tops)
&& not (isPlace (last tops))
-- | is a classical infix 'Id' with three tokens,
-- the middle one is a non-'place'
[e1, e2, e3] -> isPlace e1 && not (isPlace e2)
-- | starts and ends with a 'place'
isInfix (Id tops _ _) = not (null tops) && isPlace (head tops)
-- | has a 'place' but neither starts nor ends with one
isSurround i@(Id tops _ _) = not (null tops) && (isMixfix i)
&& not (isPlace (head tops))
&& not (isPlace (last tops))
-- | has no compound list
isNonCompound :: Id -> Bool
isNonCompound (Id _ cs _) = null cs
-- | compute a meaningful single position from an 'Id' for diagnostics
posOfId (Id ts _ ps) = let l = filter (not . isPlace) ts
-- for invisible "__ __" (only places)
-- | get a reasonable position for a list
posOf :: PosItem a => [a] -> [Pos]
posOf = concatMap get_pos
-- | get a reasonable position for a list with an additional position list
firstPos :: PosItem a => [a] -> [Pos] -> [Pos]
firstPos l ps = posOf l ++ ps
---- helper class -------------------------------------------------------
{- | This class is derivable with DrIFT.
Its main purpose is to have a function that operates on
constructors with a 'Pos' or list of 'Pos' field. During parsing, mixfix
analysis and ATermConversion this function might be very useful.
-- a Pos list should not contain nullPos
instance PosItem Token where
instance PosItem Id where