Skip to content

Commit

Permalink
feat(eo-phi-normalizer): add simple unicode escaping
Browse files Browse the repository at this point in the history
  • Loading branch information
deemp committed Nov 29, 2024
1 parent 3bc39db commit 30a402e
Showing 1 changed file with 7 additions and 2 deletions.
9 changes: 7 additions & 2 deletions eo-phi-normalizer/src/Language/EO/Phi/Rules/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}
Expand All @@ -39,7 +40,7 @@ import Control.Arrow (Arrow (first))
import Control.Monad
import Data.ByteString (ByteString)
import Data.ByteString qualified as ByteString.Strict
import Data.Char (toUpper)
import Data.Char (ord, toUpper)
import Data.HashMap.Strict qualified as HashMap
import Data.List (intercalate, minimumBy, nubBy, sortOn)
import Data.List.NonEmpty (NonEmpty (..), (<|))
Expand All @@ -52,6 +53,7 @@ import Language.EO.Phi.Syntax.Abs
import Language.EO.Phi.Syntax.Lex (Token)
import Language.EO.Phi.Syntax.Par
import Numeric (readHex, showHex)
import PyF (fmt)

-- $setup
-- >>> :set -XOverloadedStrings
Expand All @@ -78,8 +80,11 @@ parseWith parser input = parser tokens
unsafeParseWith :: ([Token] -> Either String a) -> String -> a
unsafeParseWith parser input =
case parseWith parser input of
Left parseError -> error (parseError <> "\non input\n" <> input <> "\n")
Left parseError -> error (escapeNonASCII parseError <> "\non input\n" <> escapeNonASCII input <> "\n")
Right object -> object
where
escapeNonASCII :: String -> String
escapeNonASCII = foldMap (\x -> if ord x < 256 then [x] else [fmt|\\{ord x}|])

-- | State of evaluation is not needed yet, but it might be in the future
type EvaluationState = ()
Expand Down

0 comments on commit 30a402e

Please sign in to comment.