Skip to content

Commit ad78d9d

Browse files
committed
Add support for deriving ToExpr from Show
I didn't really change the `ToExpr` class, but this adds two useful functions that allow one to implement a `ToExpr` instance if a type already has a `Show` instance.
1 parent 5efb53e commit ad78d9d

File tree

1 file changed

+51
-1
lines changed

1 file changed

+51
-1
lines changed

src/Data/TreeDiff/Parser.hs

+51-1
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,20 @@
1+
{-# LANGUAGE NamedFieldPuns #-}
12
{-# LANGUAGE ScopedTypeVariables #-}
23
-- | Utilities to parse 'Expr'.
34
--
45
-- /Note:/ we don't parse diffs.
56
module Data.TreeDiff.Parser (
6-
exprParser
7+
exprParser,
8+
showToExpr,
9+
ShowParseFailed,
10+
unsafeShowToExpr,
711
) where
812

913
import Control.Applicative (many, optional, (<|>))
14+
import Control.Exception (Exception(..))
1015
import Data.Char (chr, isAlphaNum, isPunctuation, isSymbol)
1116

17+
import GHC.Stack (HasCallStack)
1218
import Text.Parser.Char (CharParsing (anyChar, char, satisfy))
1319
import Text.Parser.Combinators (between, (<?>))
1420
import Text.Parser.Token
@@ -18,8 +24,11 @@ import Text.Parser.Token.Highlight
1824
(Highlight (Identifier, StringLiteral, Symbol))
1925

2026
import Data.TreeDiff.Expr
27+
import Text.Parsec (ParseError)
2128

29+
import qualified Control.Exception as Exception
2230
import qualified Data.TreeDiff.OMap as OMap
31+
import qualified Text.Parsec as Parsec
2332

2433
-- | Parsers for 'Expr' using @parsers@ type-classes.
2534
--
@@ -111,3 +120,44 @@ valid c = isAlphaNum c || isSymbol c || isPunctuation c
111120

112121
valid' :: Char -> Bool
113122
valid' c = valid c && c `notElem` "[](){}`\","
123+
124+
{-| Parse an `Expr` from a type's `Show` instance. This can come in handy if a
125+
type already has a `Show` instance and you don't want to have to derive
126+
`ToExpr` for that type and all of its dependencies.
127+
-}
128+
showToExpr :: Show a => a -> Either ShowParseFailed Expr
129+
showToExpr a =
130+
case Parsec.parse exprParser "" (show a) of
131+
Left exception -> Left ShowParseFailed{ exception }
132+
Right expr -> Right expr
133+
134+
instance Exception ShowParseFailed where
135+
displayException ShowParseFailed{ exception } =
136+
"Failed to parse an Expr from the output of show\n\
137+
\\n\
138+
\This might be due to the Show instance (or one of the Show instances it depends\n\
139+
\on) not being derived.\n\
140+
\\n\
141+
\Parsing error:\n\
142+
\\n\
143+
\" <> show exception
144+
145+
-- | `unsafeShowToExpr` failed to parse the output from `show` into an `Expr`
146+
--
147+
-- This usually means that the type (or one of its dependencies) has a `Show`
148+
-- instance that was not derived.
149+
newtype ShowParseFailed = ShowParseFailed{ exception :: ParseError }
150+
deriving (Show)
151+
152+
{-| You can use this to implement the `toExpr` method of the `ToExpr` class.
153+
However, this is a partial function that is only safe to use for derived
154+
`Show` instances and might fail for other types of instances.
155+
156+
If this function fails it will `Exception.throw` a `ShowParseFailed`
157+
exception.
158+
-}
159+
unsafeShowToExpr :: HasCallStack => Show a => a -> Expr
160+
unsafeShowToExpr a =
161+
case showToExpr a of
162+
Left exception -> Exception.throw exception
163+
Right expr -> expr

0 commit comments

Comments
 (0)