Browse Source

Implement IsString for (Located HaskLikeAtom)

ckoparkar 6 years ago
parent
commit
c01b118dc9
2 changed files with 10 additions and 1 deletions
  1. 6 1
      Data/SCargot/Common.hs
  2. 4 0
      Data/SCargot/Language/HaskLike.hs

+ 6 - 1
Data/SCargot/Common.hs

@@ -26,7 +26,7 @@ module Data.SCargot.Common ( -- $intro
                            , commonLispNumberAnyBase
                            , gnuM4NumberAnyBase
                              -- ** Source locations
-                           , Location(..), Located(..), located
+                           , Location(..), Located(..), located, dLocation
                            ) where
 
 #if !MIN_VERSION_base(4,8,0)
@@ -37,6 +37,7 @@ import           Data.Char
 import           Data.Text (Text)
 import qualified Data.Text as T
 import           Text.Parsec
+import           Text.Parsec.Pos  (newPos)
 import           Text.Parsec.Text (Parser)
 
 -- | Parse an identifier according to the R5RS Scheme standard. This
@@ -353,6 +354,10 @@ located parser = do
   end <- getPosition
   return $ At (Span begin end) result
 
+-- | A default location value
+dLocation :: Location
+dLocation = Span dPos dPos
+  where dPos = newPos "" 0 0
 
 {- $intro
 

+ 4 - 0
Data/SCargot/Language/HaskLike.hs

@@ -1,3 +1,4 @@
+{-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE OverloadedStrings #-}
 
 module Data.SCargot.Language.HaskLike
@@ -57,6 +58,9 @@ data HaskLikeAtom
 instance IsString HaskLikeAtom where
   fromString = HSIdent . fromString
 
+instance IsString (Located HaskLikeAtom) where
+  fromString = (At dLocation) . HSIdent . fromString
+
 -- | Parse a Haskell string literal as defined by the Haskell 2010
 -- language specification.
 parseHaskellString :: Parser Text