Remove old parser implementation

This commit is contained in:
Gabriel Gonzalez 2016-10-30 19:31:47 -07:00
parent 2b7e0f3c26
commit 9b7aa9dad3
7 changed files with 9 additions and 834 deletions

View File

@ -22,8 +22,6 @@ Description:
.
"Dhall .Core" contains the type checker and evaluator
.
"Dhall.Lexer" contains the @alex@-generated lexer for Dhall
.
"Morte.Parser" contains the parser for Dhall
.
Read "Dhall.Tutorial" to learn how to use this library
@ -60,9 +58,7 @@ Library
Dhall.Context,
Dhall.Core,
Dhall.Import,
Dhall.Lexer,
Dhall.Parser,
Dhall.Parser2,
Dhall.TypeCheck
Build-Tools: alex, happy

View File

@ -5,7 +5,7 @@ import Data.Monoid (mempty)
import Data.Traversable
import Dhall.Core (pretty, normalize)
import Dhall.Import (load)
import Dhall.Parser2 (exprFromText)
import Dhall.Parser (exprFromText)
import Options.Applicative hiding (Const)
import System.IO (stderr)
import System.Exit (exitFailure)

View File

@ -317,7 +317,7 @@ import Control.Exception (Exception)
import Data.Text.Lazy (Text)
import Data.Vector (Vector)
import Dhall.Core (Expr(..))
import Dhall.Parser2 (Src)
import Dhall.Parser (Src)
import Dhall.TypeCheck (X)
import GHC.Generics
import Numeric.Natural (Natural)
@ -330,7 +330,7 @@ import qualified Data.Text.Lazy.Builder
import qualified Data.Vector
import qualified Dhall.Core
import qualified Dhall.Import
import qualified Dhall.Parser2
import qualified Dhall.Parser
import qualified Dhall.TypeCheck
import qualified GHC.Generics
@ -361,7 +361,7 @@ input
-> IO a
-- ^ The decoded value in Haskell
input (Type {..}) text = do
expr <- throws (Dhall.Parser2.exprFromText text)
expr <- throws (Dhall.Parser.exprFromText text)
expr' <- Dhall.Import.load Nothing expr
typeExpr <- throws (Dhall.TypeCheck.typeOf (Annot expr' expected))
case extract (Dhall.Core.normalize expr') of

View File

@ -96,7 +96,7 @@ import Filesystem as Filesystem
import Lens.Micro (Lens')
import Lens.Micro.Mtl (zoom)
import Dhall.Core (Expr, Path(..))
import Dhall.Parser2 (Src)
import Dhall.Parser (Src)
import Dhall.TypeCheck (X(..))
import Network.HTTP.Client (Manager)
import Prelude hiding (FilePath)
@ -108,7 +108,7 @@ import qualified Data.Map.Strict as Map
import qualified Data.Text.Lazy as Text
import qualified Data.Text.Lazy.Builder as Builder
import qualified Data.Text.Lazy.Encoding
import qualified Dhall.Parser2
import qualified Dhall.Parser
import qualified Dhall.TypeCheck
import qualified Network.HTTP.Client as HTTP
import qualified Network.HTTP.Client.TLS as HTTP
@ -341,7 +341,7 @@ loadDynamic p = do
URL url -> readURL url
let abort err = liftIO (throwIO (Imported (p:paths) err))
case Dhall.Parser2.exprFromText bytes of
case Dhall.Parser.exprFromText bytes of
Left err -> case canonicalize (p:paths) of
URL url -> do
-- Also try the fallback in case of a parse error, since the
@ -355,7 +355,7 @@ loadDynamic p = do
-- TODO: Handle UTF8 decoding errors
let bytes' = HTTP.responseBody response
let text = Data.Text.Lazy.Encoding.decodeUtf8 bytes'
case Dhall.Parser2.exprFromText text of
case Dhall.Parser.exprFromText text of
Left _ -> liftIO (abort err)
Right expr -> return expr
_ -> liftIO (abort err)

View File

@ -1,423 +0,0 @@
{
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
-- | Lexing logic for the Dhall language
module Dhall.Lexer (
-- * Lexer
lexer
-- * Types
, Token(..)
-- * Re-exports
, Alex
, AlexPosn(..)
, alexError
, alexGetInput
, runAlex
) where
import Data.ByteString.Lazy (ByteString)
import Data.Monoid ((<>))
import Data.Text.Buildable (Buildable(..))
import Data.Text.Lazy (Text)
import Data.Text.Lazy.Builder (Builder)
import Filesystem.Path (FilePath)
import Numeric.Natural (Natural)
import Prelude hiding (FilePath)
import qualified Data.ByteString.Lazy
import qualified Data.ByteString.Lex.Fractional
import qualified Data.ByteString.Lex.Integral
import qualified Data.Text
import qualified Data.Text.Buildable
import qualified Data.Text.Lazy
import qualified Data.Text.Lazy.Encoding
import qualified Data.Text.Lazy.Builder
import qualified Filesystem.Path.CurrentOS
import qualified NeatInterpolation
}
%wrapper "monad-bytestring"
$digit = 0-9
-- Same as Haskell
$opchar = [\!\#\$\%\&\*\+\.\/\<\=\>\?\@\\\^\|\-\~]
$fst = [A-Za-z\_]
$labelchar = [A-Za-z0-9\_\/]
$nonwhite = ~$white
tokens :-
$white+ ;
"--".* ;
"(" { emit OpenParen }
")" { emit CloseParen }
"{" { emit OpenBrace }
"}" { emit CloseBrace }
"<" { emit OpenAngle }
">" { emit CloseAngle }
"{=}" { emit EmptyRecordLit }
"[" { emit OpenBracket }
"]" { emit CloseBracket }
":" { emit Colon }
"," { emit Comma }
"|" { emit Bar }
"." { emit Dot }
"=" { emit Equals }
"&&" { emit And }
"/\" | "∧" { emit Merge }
"||" { emit Or }
"==" { emit DoubleEquals }
"/=" { emit SlashEquals }
"+" { emit Plus }
"++" { emit DoublePlus }
"*" { emit Star }
"@" { emit At }
"let" { emit Let }
"in" { emit In }
"Type" { emit Type }
"Kind" { emit Kind }
"->" | "→" { emit Arrow }
"forall" | "∀" { emit Forall }
"\" | "λ" { emit Lambda }
"Bool" { emit Bool }
"True" { emit True_ }
"False" { emit False_ }
"apply" { emit Apply }
"if" { emit If }
"then" { emit Then }
"else" { emit Else }
"Natural" { emit Natural }
"Natural/fold" { emit NaturalFold }
"Natural/build" { emit NaturalBuild }
"Natural/isZero" { emit NaturalIsZero }
"Natural/even" { emit NaturalEven }
"Natural/odd" { emit NaturalOdd }
"Integer" { emit Integer }
"Double" { emit Double }
"Text" { emit Text }
"List" { emit List }
"List/build" { emit ListBuild }
"List/fold" { emit ListFold }
"List/length" { emit ListLength }
"List/head" { emit ListHead }
"List/last" { emit ListLast }
"List/indexed" { emit ListIndexed }
"List/reverse" { emit ListReverse }
"Maybe" { emit Maybe }
"Maybe/fold" { emit MaybeFold }
\" ([^\"] | \\.)* \" { capture (TextLit . str) }
$fst $labelchar* | "(" $opchar+ ")" { capture (Label . toText) }
\-? $digit+ { capture (Number . toInt) }
$digit+ (\. $digit+)? ([eE][\+\-]? $digit+)?
{ capture (DoubleLit . toDouble) }
"+" $digit+ { capture (NaturalLit . toNat) }
"https://" $nonwhite+ { capture (URL . toText) }
"http://" $nonwhite+ { capture (URL . toText) }
"/" $nonwhite+ { capture (File . toFile 0 ) }
"./" $nonwhite+ { capture (File . toFile 2 ) }
"../" $nonwhite+ { capture (File . toFile 0 ) }
{
emit :: Token -> AlexAction Token
emit x = \_ _ -> return x
alexEOF :: Alex Token
alexEOF = return EOF
capture :: (ByteString -> Token) -> AlexAction Token
capture k (_, _, rest, _) len = return (k bytes)
where
bytes = Data.ByteString.Lazy.take len rest
toInt :: ByteString -> Integer
toInt bytes =
case m of
Just (n, _) -> n
Nothing -> error "toInt: internal error"
where
m = Data.ByteString.Lex.Integral.readSigned
Data.ByteString.Lex.Integral.readDecimal
(Data.ByteString.Lazy.toStrict bytes)
toDouble :: ByteString -> Double
toDouble bytes =
case Data.ByteString.Lex.Fractional.readExponential bytes' of
Just (n, _) -> n
_ -> error "toDouble: internal error"
where
bytes' = Data.ByteString.Lazy.toStrict bytes
toNat :: ByteString -> Natural
toNat = fromIntegral . toInt . Data.ByteString.Lazy.drop 1
toFile :: Int64 -> ByteString -> FilePath
toFile n =
Filesystem.Path.CurrentOS.fromText
. Data.Text.Lazy.toStrict
. Data.Text.Lazy.Encoding.decodeUtf8
. Data.ByteString.Lazy.drop n
toText :: ByteString -> Text
toText = Data.Text.Lazy.Encoding.decodeUtf8
-- TODO: Properly handle errors here
str :: ByteString -> Builder
str = Data.Text.Lazy.Builder.fromLazyText
. read
. Data.Text.Lazy.unpack
. Data.Text.Lazy.Encoding.decodeUtf8
-- | `Alex` action for reading the next token
lexer :: (Token -> Alex a) -> Alex a
lexer k = alexMonadScan' >>= k
{-| This was forked from the auto-generated `alexMonadScan` function to improve
the error message
-}
alexMonadScan' :: Alex Token
alexMonadScan' = do
inp@(_,_,str,n) <- alexGetInput
sc <- alexGetStartCode
case alexScan inp sc of
AlexEOF -> alexEOF
AlexError ((AlexPn _ line column),w8,bytes,_) ->
alexError (Data.Text.unpack [NeatInterpolation.text|
Error: Lexing failed
Explanation: The source code is normally decomposed into a sequence of tokens.
For example, this input:
λ(a : Type) → a
... is split into these tokens:
[ "λ", "(", "a", ":", "Type", ")", "→", "a" ]
However, some characters in your program could not be assigned to a recognized
token
Unrecognized input:
↳ $txt0
... beginning at:
↳ Line $txt1, Column $txt2
|])
where
txt0 = Data.Text.pack (show input)
input =
Data.Text.Lazy.take 76
(Data.Text.Lazy.cons w8
(Data.Text.Lazy.Encoding.decodeUtf8 bytes) )
txt1 = Data.Text.pack (show line)
txt2 = Data.Text.pack (show column)
AlexSkip inp' len -> do
alexSetInput inp'
alexMonadScan'
AlexToken inp'@(_,_,_,n') _ action -> do
alexSetInput inp'
action (ignorePendingBytes inp) len
where
len = n'-n
-- | Token type, used to communicate between the lexer and parser
data Token
= OpenParen
| CloseParen
| OpenBrace
| CloseBrace
| OpenAngle
| CloseAngle
| EmptyRecordLit
| OpenBracket
| CloseBracket
| Colon
| Comma
| Bar
| Dot
| Equals
| And
| Merge
| Or
| DoubleEquals
| SlashEquals
| Plus
| DoublePlus
| At
| Star
| Let
| In
| Type
| Kind
| Arrow
| Lambda
| Forall
| Bool
| True_
| False_
| Apply
| If
| Then
| Else
| Natural
| NaturalLit Natural
| NaturalFold
| NaturalBuild
| NaturalIsZero
| NaturalEven
| NaturalOdd
| Integer
| Text
| Double
| DoubleLit Double
| List
| ListBuild
| ListFold
| ListLength
| ListHead
| ListLast
| ListIndexed
| ListReverse
| Maybe
| MaybeFold
| TextLit Builder
| Label Text
| Number Integer
| File FilePath
| URL Text
| EOF
deriving (Eq, Show)
instance Buildable Token where
build OpenParen
= "("
build CloseParen
= ")"
build OpenBrace
= "{"
build CloseBrace
= "}"
build OpenAngle
= "<"
build CloseAngle
= ">"
build EmptyRecordLit
= "{=}"
build OpenBracket
= "["
build CloseBracket
= "]"
build Colon
= ":"
build Comma
= ","
build Bar
= "|"
build Dot
= "."
build Equals
= "="
build And
= "&&"
build Merge
= "∧"
build Or
= "||"
build DoubleEquals
= "=="
build SlashEquals
= "/="
build Plus
= "+"
build DoublePlus
= "++"
build At
= "@"
build Star
= "*"
build Let
= "let"
build In
= "in"
build Type
= "Type"
build Kind
= "Kind"
build Arrow
= "→"
build Lambda
= "λ"
build Forall
= "∀"
build Bool
= "Bool"
build True_
= "True"
build False_
= "False"
build Apply
= "apply"
build If
= "if"
build Then
= "then"
build Else
= "else"
build Natural
= "Natural"
build (NaturalLit n)
= "+" <> Data.Text.Buildable.build (fromIntegral n :: Integer)
build NaturalFold
= "Natural/fold"
build NaturalBuild
= "Natural/build"
build NaturalIsZero
= "Natural/isZero"
build NaturalEven
= "Natural/even"
build NaturalOdd
= "Natural/odd"
build Integer
= "Integer"
build Text
= "Text"
build Double
= "Double"
build (DoubleLit n)
= Data.Text.Buildable.build n
build List
= "List"
build ListBuild
= "List/build"
build ListLength
= "List/length"
build ListHead
= "List/head"
build ListLast
= "List/last"
build ListIndexed
= "List/indexed"
build ListReverse
= "List/reverse"
build ListFold
= "List/fold"
build Maybe
= "Maybe"
build MaybeFold
= "Maybe/fold"
build (TextLit t)
= Data.Text.Buildable.build (show t)
build (Label t)
= Data.Text.Buildable.build t
build (Number n)
= Data.Text.Buildable.build (fromIntegral n :: Integer)
build (File f)
= Data.Text.Buildable.build (Filesystem.Path.CurrentOS.encodeString f)
build (URL t)
= Data.Text.Buildable.build t
build EOF
= "EOF"
}

View File

@ -2,7 +2,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
module Dhall.Parser2 (
module Dhall.Parser (
-- * Parser
exprFromText

View File

@ -1,398 +0,0 @@
{
-- | Parsing logic for the Dhall language
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Dhall.Parser (
-- * Parser
exprFromBytes
-- * Types
, Src(..)
, ParseError(..)
) where
import Control.Exception (Exception)
import Data.ByteString.Lazy (ByteString)
import Data.Monoid ((<>))
import Data.Text.Lazy (Text)
import Data.Typeable (Typeable)
import Dhall.Core
import Dhall.Lexer (Alex, AlexPosn(..), Token)
import qualified Data.Map
import qualified Data.Maybe
import qualified Data.Vector
import qualified Data.Text
import qualified Data.Text.Buildable
import qualified Data.Text.Lazy
import qualified Data.Text.Lazy.Builder
import qualified Data.Text.Lazy.Encoding
import qualified Dhall.Lexer
import qualified NeatInterpolation
}
%name expr
%tokentype { Token }
%error { parseError }
%lexer { Dhall.Lexer.lexer } { Dhall.Lexer.EOF }
%monad { Alex }
%token
'(' { Dhall.Lexer.OpenParen }
')' { Dhall.Lexer.CloseParen }
'{' { Dhall.Lexer.OpenBrace }
'}' { Dhall.Lexer.CloseBrace }
'<' { Dhall.Lexer.OpenAngle }
'>' { Dhall.Lexer.CloseAngle }
'{=}' { Dhall.Lexer.EmptyRecordLit }
'[' { Dhall.Lexer.OpenBracket }
']' { Dhall.Lexer.CloseBracket }
':' { Dhall.Lexer.Colon }
',' { Dhall.Lexer.Comma }
'|' { Dhall.Lexer.Bar }
'.' { Dhall.Lexer.Dot }
'=' { Dhall.Lexer.Equals }
'&&' { Dhall.Lexer.And }
'∧' { Dhall.Lexer.Merge }
'||' { Dhall.Lexer.Or }
'==' { Dhall.Lexer.DoubleEquals }
'/=' { Dhall.Lexer.SlashEquals }
'+' { Dhall.Lexer.Plus }
'++' { Dhall.Lexer.DoublePlus }
'*' { Dhall.Lexer.Star }
'@' { Dhall.Lexer.At }
'let' { Dhall.Lexer.Let }
'in' { Dhall.Lexer.In }
'Type' { Dhall.Lexer.Type }
'Kind' { Dhall.Lexer.Kind }
'->' { Dhall.Lexer.Arrow }
'forall' { Dhall.Lexer.Forall }
'\\' { Dhall.Lexer.Lambda }
'Bool' { Dhall.Lexer.Bool }
'True' { Dhall.Lexer.True_ }
'False' { Dhall.Lexer.False_ }
'apply' { Dhall.Lexer.Apply }
'if' { Dhall.Lexer.If }
'then' { Dhall.Lexer.Then }
'else' { Dhall.Lexer.Else }
'Natural' { Dhall.Lexer.Natural }
'Natural/fold' { Dhall.Lexer.NaturalFold }
'Natural/build' { Dhall.Lexer.NaturalBuild }
'Natural/isZero' { Dhall.Lexer.NaturalIsZero }
'Natural/even' { Dhall.Lexer.NaturalEven }
'Natural/odd' { Dhall.Lexer.NaturalOdd }
'Integer' { Dhall.Lexer.Integer }
'Double' { Dhall.Lexer.Double }
'Text' { Dhall.Lexer.Text }
'List' { Dhall.Lexer.List }
'List/build' { Dhall.Lexer.ListBuild }
'List/fold' { Dhall.Lexer.ListFold }
'List/length' { Dhall.Lexer.ListLength }
'List/head' { Dhall.Lexer.ListHead }
'List/last' { Dhall.Lexer.ListLast }
'List/indexed' { Dhall.Lexer.ListIndexed }
'List/reverse' { Dhall.Lexer.ListReverse }
'Maybe' { Dhall.Lexer.Maybe }
'Maybe/fold' { Dhall.Lexer.MaybeFold }
text { Dhall.Lexer.TextLit $$ }
label { Dhall.Lexer.Label $$ }
number { Dhall.Lexer.Number $$ }
double { Dhall.Lexer.DoubleLit $$ }
natural { Dhall.Lexer.NaturalLit $$ }
url { Dhall.Lexer.URL $$ }
file { Dhall.Lexer.File $$ }
%right '=='
%right '/='
%right '||'
%right '&&'
%right '+'
%right '*'
%right '++'
%%
Expr0
: Expr1 ':' Expr0
{ Annot $1 $3 }
| Expr1
{ $1 }
Expr1
: '\\' '(' label ':' Expr0 ')' '->' Expr1
{ Lam $3 $5 $8 }
| 'if' Expr0 'then' Expr1 'else' Expr1
{ BoolIf $2 $4 $6 }
| Expr2 '->' Expr1
{ Pi "_" $1 $3 }
| 'forall' '(' label ':' Expr0 ')' '->' Expr1
{ Pi $3 $5 $8 }
| 'let' label '=' Expr0 'in' Expr1
{ Let $2 Nothing $4 $6 }
| 'let' label ':' Expr0 '=' Expr0 'in' Expr1
{ Let $2 (Just $4) $6 $8 }
| '[' Elems ']' ':' ListLike Expr6
{ $5 $6 (Data.Vector.fromList $2) }
| 'apply' Expr6 Expr6 ':' Expr5
{ Apply $2 $3 $5 }
| Expr2
{ $1 }
ListLike
: 'List'
{ ListLit }
| 'Maybe'
{ MaybeLit }
Expr2
: Expr2 '==' Expr2
{ BoolEQ $1 $3 }
| Expr2 '/=' Expr2
{ BoolNE $1 $3 }
| Expr3
{ $1 }
Expr3
: Expr3 '||' Expr3
{ BoolOr $1 $3 }
| Expr3 '+' Expr3
{ NaturalPlus $1 $3 }
| Expr3 '++' Expr3
{ TextAppend $1 $3 }
| Expr4
{ $1 }
Expr4
: Expr4 '&&' Expr4
{ BoolAnd $1 $3 }
| Expr4 '*' Expr4
{ NaturalTimes $1 $3 }
| Expr4 '∧' Expr4
{ Merge $1 $3 }
| Expr5
{ $1 }
Expr5
: Expr5 Expr6
{ App $1 $2 }
| Expr6
{ $1 }
Expr6
: Var
{ Var $1 }
| Const
{ Const $1 }
| 'Bool'
{ Bool }
| 'Natural'
{ Natural }
| 'Natural/fold'
{ NaturalFold }
| 'Natural/build'
{ NaturalBuild }
| 'Natural/isZero'
{ NaturalIsZero }
| 'Natural/even'
{ NaturalEven }
| 'Natural/odd'
{ NaturalOdd }
| 'Integer'
{ Integer }
| 'Double'
{ Double }
| 'Text'
{ Text }
| 'List'
{ List }
| 'List/build'
{ ListBuild }
| 'List/fold'
{ ListFold }
| 'List/length'
{ ListLength }
| 'List/head'
{ ListHead }
| 'List/last'
{ ListLast }
| 'List/indexed'
{ ListIndexed }
| 'List/reverse'
{ ListReverse }
| 'Maybe'
{ Maybe }
| 'Maybe/fold'
{ MaybeFold }
| 'True'
{ BoolLit True }
| 'False'
{ BoolLit False }
| number
{ IntegerLit (fromIntegral $1) }
| natural
{ NaturalLit $1 }
| double
{ DoubleLit $1 }
| text
{ TextLit $1 }
| Record
{ $1 }
| RecordLit
{ $1 }
| Union
{ $1 }
| UnionLit
{ $1 }
| Import
{ Embed $1 }
| Expr6 '.' label
{ Field $1 $3 }
| '(' Expr0 ')'
{ $2 }
Const
: 'Type'
{ Type }
| 'Kind'
{ Kind }
Var
: label
{ V $1 0 }
| label '@' number
{ V $1 $3 }
Elems
: ElemsRev
{ reverse $1 }
ElemsRev
: {- empty -}
{ [] }
| Expr0
{ [$1] }
| ElemsRev ',' Expr0
{ $3 : $1 }
RecordLit
: '{=}'
{ RecordLit (Data.Map.fromList []) }
| '{' FieldValues '}'
{ RecordLit (Data.Map.fromList $2) }
FieldValues
: FieldValuesRev
{ reverse $1 }
FieldValuesRev
: FieldValue
{ [$1] }
| FieldValuesRev ',' FieldValue
{ $3 : $1 }
FieldValue
: label '=' Expr0
{ ($1, $3) }
Record
: '{' FieldTypes '}'
{ Record (Data.Map.fromList $2) }
FieldTypes
: FieldTypesRev
{ reverse $1 }
FieldTypesRev
: {- empty -}
{ [] }
| FieldType
{ [$1] }
| FieldTypesRev ',' FieldType
{ $3 : $1 }
FieldType
: label ':' Expr0
{ ($1, $3) }
Union
: '<' AlternativeTypes '>'
{ Union (Data.Map.fromList $2) }
AlternativeTypes
: AlternativeTypesRev
{ reverse $1 }
AlternativeTypesRev
: {- empty -}
{ [] }
| AlternativeType
{ [$1] }
| AlternativeTypesRev '|' AlternativeType
{ $3 : $1 }
AlternativeType
: label ':' Expr0
{ ($1, $3) }
UnionLit
: '<' label '=' Expr0 '>'
{ UnionLit $2 $4 Data.Map.empty }
| '<' label '=' Expr0 '|' AlternativeTypes '>'
{ UnionLit $2 $4 (Data.Map.fromList $6) }
Import
: file
{ File $1 }
| url
{ URL $1 }
{
data Src = Src deriving (Typeable)
parseError :: Token -> Alex a
parseError token = do
(AlexPn _ line column, _, bytes, _) <- Dhall.Lexer.alexGetInput
Dhall.Lexer.alexError (Data.Text.unpack (msg line column bytes))
where
msg line column bytes = [NeatInterpolation.text|
Error: Parsing failed
Explanation: The source code is decomposed into a sequence of tokens and these
tokens are then parsed to generate a syntax tree
The parsing step failed to generate a syntax tree due to this unexpected token:
↳ $txt0
... ending at:
↳ Line $txt1, Column $txt2
... with the following unconsumed input:
↳ $txt3
|]
where
txt0 =
Data.Text.Lazy.toStrict
(Data.Text.Lazy.Builder.toLazyText
(Data.Text.Buildable.build token) )
txt1 = Data.Text.pack (show line)
txt2 = Data.Text.pack (show column)
txt3 = Data.Text.take 76 (Data.Text.pack (show bytes))
-- | A parsing error
newtype ParseError = ParseError Text
deriving (Typeable)
instance Show ParseError where
show (ParseError txt) = Data.Text.Lazy.unpack txt
instance Exception ParseError
{-| Parse an expression from a `ByteString` containing a UTF8-encoded Dhall
program
-}
exprFromBytes :: ByteString -> Either ParseError (Expr Src Path)
exprFromBytes bytes = case Dhall.Lexer.runAlex bytes expr of
Left str -> Left (ParseError (Data.Text.Lazy.pack str))
Right e -> Right e
}