Skip to content

Commit

Permalink
Make error messages more clear
Browse files Browse the repository at this point in the history
  • Loading branch information
WoWaster committed Oct 26, 2024
1 parent 73c9bd5 commit 4d56a67
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 2 deletions.
3 changes: 3 additions & 0 deletions lamagraph-compiler/lamagraph-compiler.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,7 @@ library
, lens
, prettyprinter
, relude
, string-interpolate
default-language: GHC2021

executable lamagraph-compiler-exe
Expand All @@ -84,6 +85,7 @@ executable lamagraph-compiler-exe
, lens
, prettyprinter
, relude
, string-interpolate
default-language: GHC2021

test-suite lamagraph-compiler-test
Expand Down Expand Up @@ -115,6 +117,7 @@ test-suite lamagraph-compiler-test
, lens
, prettyprinter
, relude
, string-interpolate
, tasty
, tasty-golden
, tasty-hedgehog
Expand Down
1 change: 1 addition & 0 deletions lamagraph-compiler/package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ dependencies:
- extra
- lens
- prettyprinter
- string-interpolate

language: GHC2021

Expand Down
8 changes: 6 additions & 2 deletions lamagraph-compiler/src/Lamagraph/Compiler/PrettyLml.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE QuasiQuotes #-}
{-# OPTIONS_GHC -Wno-orphans #-}

{- | Orphan instances for pretty-printing LamagraphML
Expand All @@ -8,6 +9,7 @@ module Lamagraph.Compiler.PrettyLml () where

import Relude

import Data.String.Interpolate (i)
import Data.Text qualified as T
import Prettyprinter

Expand All @@ -17,7 +19,9 @@ import Lamagraph.Compiler.Syntax

prettyADTVar :: LLmlType (LmlcPass pass) -> Doc ann
prettyADTVar (L _ (LmlTyVar _ varName)) = "'" <> pretty varName
prettyADTVar _ = error "Internal pretty-printer error: cannot have complex types in type parameters"
prettyADTVar t =
error
[i|Internal pretty-printer error: expected list of type variables in AST as a type parameters, but got #{pretty t}|]

prettyADTVars :: [LLmlType (LmlcPass pass)] -> Doc ann
prettyADTVars [] = emptyDoc
Expand All @@ -31,7 +35,7 @@ prettyChar '\'' = "\\\'"
prettyChar '\n' = "\\\n"
prettyChar c
| c `elem` ['\32' .. '\127'] = pretty c
| otherwise = error "Internal pretty-printer error: trying to print unsupported character"
| otherwise = error [i|Internal pretty-printer error: trying to print unsupported in LML character "#{c}"|]

prettyString :: Text -> Doc ann
prettyString str = mconcat $ map prettyChar (toString str)
Expand Down

0 comments on commit 4d56a67

Please sign in to comment.