hnix/src/Nix/Render.hs

36 lines
1.2 KiB
Haskell
Raw Normal View History

2018-04-07 21:02:50 +02:00
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
2018-04-07 21:02:50 +02:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
2018-04-07 21:02:50 +02:00
module Nix.Render where
2018-04-07 21:02:50 +02:00
2018-04-10 18:03:24 +02:00
import Data.ByteString (ByteString)
import Data.List.NonEmpty (NonEmpty((:|)))
import qualified Data.Set as Set
import Data.Void
import Nix.Expr.Types.Annotated
import Text.Megaparsec.Error
import Text.Megaparsec.Pos (SourcePos(..))
import Text.PrettyPrint.ANSI.Leijen
2018-04-07 21:02:50 +02:00
class Monad m => MonadFile m where
readFile :: FilePath -> m ByteString
posAndMsg :: SourcePos -> Doc -> ParseError t Void
posAndMsg beg msg =
FancyError (beg :| [])
(Set.fromList [ErrorFail (show msg) :: ErrorFancy Void])
renderLocation :: MonadFile m => SrcSpan -> Doc -> m Doc
renderLocation (SrcSpan beg@(SourcePos "<string>" _ _) _) msg =
return $ text $ init $ parseErrorPretty @Char (posAndMsg beg msg)
renderLocation (SrcSpan beg@(SourcePos path _ _) _) msg = do
contents <- Nix.Render.readFile path
return $ text $ init $ parseErrorPretty' contents (posAndMsg beg msg)