Skip to content

Commit a313773

Browse files
committed
fix: Remove unsafe FromJSON Name instance
Because it used `deriving newtype`, this instance constructed names without any validation, similarly to `unsafeMkName`. While we don't currently have any name validation, we expect that we will soon move to a "smart constructor" approach, ripping out most uses of `unsafeMkName`. We don't then want `fromJSON @Name` to remain as a validation-skipping backdoor. An alternative would be to use our smart constructor (i.e. `safeMkName`) in a manual implementation of `fromJSON`. But given that the instance is unused (other than to define more unused instances for types which contain `Name`), we may as well just remove it. N.B. This instance has been around since our old prototype frontend, and may have been useful back then.
1 parent c8df8fd commit a313773

25 files changed

+65
-68
lines changed

primer/src/Primer/API.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1170,7 +1170,7 @@ data ApplyActionBody = ApplyActionBody
11701170
, option :: Available.Option
11711171
}
11721172
deriving (Generic, Show)
1173-
deriving (FromJSON, ToJSON) via PrimerJSON ApplyActionBody
1173+
deriving (ToJSON) via PrimerJSON ApplyActionBody
11741174

11751175
applyActions :: (MonadIO m, MonadThrow m, MonadAPILog l m) => ExprTreeOpts -> SessionId -> [ProgAction] -> PrimerM m Prog
11761176
applyActions opts sid actions =
@@ -1185,7 +1185,7 @@ data Selection = Selection
11851185
, node :: Maybe NodeSelection
11861186
}
11871187
deriving (Eq, Show, Generic)
1188-
deriving (FromJSON, ToJSON) via PrimerJSON Selection
1188+
deriving (ToJSON) via PrimerJSON Selection
11891189

11901190
viewSelection :: App.Selection -> Selection
11911191
viewSelection App.Selection{..} = Selection{def = selectedDef, node = viewNodeSelection <$> selectedNode}

primer/src/Primer/Action/Actions.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ module Primer.Action.Actions (
66

77
import Foreword
88

9-
import Data.Aeson (FromJSON (..), ToJSON (..), Value)
9+
import Data.Aeson (ToJSON (..), Value)
1010
import Primer.Core (PrimCon)
1111
import Primer.Core.Meta (ID, TmVarRef, ValConName)
1212
import Primer.JSON (CustomJSON (..), PrimerJSON)
@@ -102,9 +102,9 @@ data Action
102102
| -- | Rename a case binding
103103
RenameCaseBinding Text
104104
deriving (Eq, Show, Generic)
105-
deriving (FromJSON, ToJSON) via PrimerJSON Action
105+
deriving (ToJSON) via PrimerJSON Action
106106

107107
-- | Core movements
108108
data Movement = Child1 | Child2 | Parent | Branch ValConName
109109
deriving (Eq, Show, Generic)
110-
deriving (FromJSON, ToJSON) via PrimerJSON Movement
110+
deriving (ToJSON) via PrimerJSON Movement

primer/src/Primer/Action/Errors.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ module Primer.Action.Errors (ActionError (..)) where
99

1010
import Foreword
1111

12-
import Data.Aeson (FromJSON (..), ToJSON (..))
12+
import Data.Aeson (ToJSON (..))
1313
import Primer.Action.Actions (Action)
1414
import Primer.Action.Available qualified as Available
1515
import Primer.Core (Expr, GVarName, ID, LVarName, ModuleName, Type)
@@ -63,4 +63,4 @@ data ActionError
6363
| NeedChar Available.Option
6464
| NoNodeSelection
6565
deriving (Eq, Show, Generic)
66-
deriving (FromJSON, ToJSON) via PrimerJSON ActionError
66+
deriving (ToJSON) via PrimerJSON ActionError

primer/src/Primer/Action/ProgAction.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ module Primer.Action.ProgAction (ProgAction (..)) where
1010

1111
import Foreword
1212

13-
import Data.Aeson (FromJSON (..), ToJSON (..))
13+
import Data.Aeson (ToJSON (..))
1414
import Primer.Action.Actions (Action)
1515
import Primer.Core.Meta (GVarName, ID, ModuleName, TyConName, TyVarName, ValConName)
1616
import Primer.Core.Type (Type')
@@ -64,4 +64,4 @@ data ProgAction
6464
| -- | Renames an editable module (will return an error if asked to rename an imported module)
6565
RenameModule ModuleName (NonEmpty Text)
6666
deriving (Eq, Show, Generic)
67-
deriving (FromJSON, ToJSON) via PrimerJSON ProgAction
67+
deriving (ToJSON) via PrimerJSON ProgAction

primer/src/Primer/Action/ProgError.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@ module Primer.Action.ProgError (ProgError (..)) where
22

33
import Foreword
44

5-
import Data.Aeson (FromJSON (..), ToJSON (..))
5+
import Data.Aeson (ToJSON (..))
66
import Primer.Action.Errors (ActionError)
77
import Primer.Core.Meta (GVarName, ModuleName, TyConName, TyVarName, ValConName)
88
import Primer.Eval.EvalError (EvalError)
@@ -44,4 +44,4 @@ data ProgError
4444
| -- | Cannot edit an imported module
4545
ModuleReadonly ModuleName
4646
deriving (Eq, Show, Generic)
47-
deriving (FromJSON, ToJSON) via PrimerJSON ProgError
47+
deriving (ToJSON) via PrimerJSON ProgError

primer/src/Primer/App.hs

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -230,7 +230,7 @@ data Prog = Prog
230230
, progLog :: Log -- The log of all actions
231231
}
232232
deriving (Eq, Show, Generic)
233-
deriving (FromJSON, ToJSON) via PrimerJSON Prog
233+
deriving (ToJSON) via PrimerJSON Prog
234234

235235
-- | The default 'Prog'. It has no imports, no definitions, no current
236236
-- 'Selection', and an empty 'Log'. Smart holes are enabled.
@@ -379,7 +379,7 @@ allDefs = fmap snd . progAllDefs
379379
-- Items are stored in reverse order so it's quick to add new ones.
380380
newtype Log = Log {unlog :: [[ProgAction]]}
381381
deriving (Eq, Show, Generic)
382-
deriving (FromJSON, ToJSON) via PrimerJSON Log
382+
deriving (ToJSON) via PrimerJSON Log
383383

384384
-- | The default (empty) 'Log'.
385385
defaultLog :: Log
@@ -393,7 +393,7 @@ data Selection = Selection
393393
, selectedNode :: Maybe NodeSelection
394394
}
395395
deriving (Eq, Show, Generic, Data)
396-
deriving (FromJSON, ToJSON) via PrimerJSON Selection
396+
deriving (ToJSON) via PrimerJSON Selection
397397

398398
-- | A selected node, in the body or type signature of some definition.
399399
-- We have the following invariant: @nodeType = SigNode ==> isRight meta@
@@ -402,7 +402,7 @@ data NodeSelection = NodeSelection
402402
, meta :: Either ExprMeta TypeMeta
403403
}
404404
deriving (Eq, Show, Generic, Data)
405-
deriving (FromJSON, ToJSON) via PrimerJSON NodeSelection
405+
deriving (ToJSON) via PrimerJSON NodeSelection
406406

407407
instance HasID NodeSelection where
408408
_id =
@@ -415,37 +415,37 @@ data MutationRequest
415415
= Undo
416416
| Edit [ProgAction]
417417
deriving (Eq, Show, Generic)
418-
deriving (FromJSON, ToJSON) via PrimerJSON MutationRequest
418+
deriving (ToJSON) via PrimerJSON MutationRequest
419419

420420
data EvalReq = EvalReq
421421
{ evalReqExpr :: Expr
422422
, evalReqRedex :: ID
423423
}
424424
deriving (Eq, Show, Generic)
425-
deriving (FromJSON, ToJSON) via PrimerJSON EvalReq
425+
deriving (ToJSON) via PrimerJSON EvalReq
426426

427427
data EvalResp = EvalResp
428428
{ evalRespExpr :: Expr
429429
, evalRespRedexes :: [ID]
430430
, evalRespDetail :: EvalDetail
431431
}
432432
deriving (Eq, Show, Generic)
433-
deriving (FromJSON, ToJSON) via PrimerJSON EvalResp
433+
deriving (ToJSON) via PrimerJSON EvalResp
434434

435435
data EvalFullReq = EvalFullReq
436436
{ evalFullReqExpr :: Expr
437437
, evalFullCxtDir :: Dir -- is this expression in a syn/chk context, so we can tell if is an embedding.
438438
, evalFullMaxSteps :: TerminationBound
439439
}
440440
deriving (Eq, Show, Generic)
441-
deriving (FromJSON, ToJSON) via PrimerJSON EvalFullReq
441+
deriving (ToJSON) via PrimerJSON EvalFullReq
442442

443443
-- If we time out, we still return however far we got
444444
data EvalFullResp
445445
= EvalFullRespTimedOut Expr
446446
| EvalFullRespNormal Expr
447447
deriving (Eq, Show, Generic)
448-
deriving (FromJSON, ToJSON) via PrimerJSON EvalFullResp
448+
deriving (ToJSON) via PrimerJSON EvalFullResp
449449

450450
-- * Request handlers
451451

@@ -1049,7 +1049,7 @@ data App = App
10491049
, initialState :: AppState
10501050
}
10511051
deriving (Eq, Show, Generic)
1052-
deriving (FromJSON, ToJSON) via PrimerJSON App
1052+
deriving (ToJSON) via PrimerJSON App
10531053

10541054
-- Internal app state. Note that this type is not exported, as we want
10551055
-- to guarantee that the counters are kept in sync with the 'Prog',
@@ -1061,7 +1061,7 @@ data AppState = AppState
10611061
, prog :: Prog
10621062
}
10631063
deriving (Eq, Show, Generic)
1064-
deriving (FromJSON, ToJSON) via PrimerJSON AppState
1064+
deriving (ToJSON) via PrimerJSON AppState
10651065

10661066
-- | Construct an 'App' from an 'ID' and a 'Prog'.
10671067
--

primer/src/Primer/Core.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,7 @@ data TypeCache
9595
| TCChkedAt (Type' ())
9696
| TCEmb TypeCacheBoth
9797
deriving (Eq, Show, Generic, Data)
98-
deriving (FromJSON, ToJSON) via PrimerJSON TypeCache
98+
deriving (ToJSON) via PrimerJSON TypeCache
9999
deriving anyclass (NFData)
100100

101101
-- We were checking at the first, but term was synthesisable and synth'd the
@@ -104,7 +104,7 @@ data TypeCache
104104
-- though, to make it clear what each one is!
105105
data TypeCacheBoth = TCBoth {tcChkedAt :: Type' (), tcSynthed :: Type' ()}
106106
deriving (Eq, Show, Generic, Data)
107-
deriving (FromJSON, ToJSON) via PrimerJSON TypeCacheBoth
107+
deriving (ToJSON) via PrimerJSON TypeCacheBoth
108108
deriving anyclass (NFData)
109109

110110
-- TODO `_chkedAt` and `_synthed` should be `AffineTraversal`s,
@@ -182,7 +182,7 @@ data Expr' a b
182182
| Case a (Expr' a b) [CaseBranch' a b] -- See Note [Case]
183183
| PrimCon a PrimCon
184184
deriving (Eq, Show, Data, Generic)
185-
deriving (FromJSON, ToJSON) via PrimerJSON (Expr' a b)
185+
deriving (ToJSON) via PrimerJSON (Expr' a b)
186186
deriving anyclass (NFData)
187187

188188
-- Note [Synthesisable constructors]
@@ -257,7 +257,7 @@ data CaseBranch' a b
257257
(Expr' a b)
258258
-- ^ right hand side
259259
deriving (Eq, Show, Data, Generic)
260-
deriving (FromJSON, ToJSON) via PrimerJSON (CaseBranch' a b)
260+
deriving (ToJSON) via PrimerJSON (CaseBranch' a b)
261261
deriving anyclass (NFData)
262262

263263
-- | Variable bindings
@@ -267,7 +267,7 @@ type Bind = Bind' ExprMeta
267267

268268
data Bind' a = Bind a LVarName
269269
deriving (Eq, Show, Data, Generic)
270-
deriving (FromJSON, ToJSON) via PrimerJSON (Bind' a)
270+
deriving (ToJSON) via PrimerJSON (Bind' a)
271271
deriving anyclass (NFData)
272272

273273
bindName :: Bind' a -> LVarName

primer/src/Primer/Core/Meta.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ trivialMeta id = Meta id Nothing Nothing
7777

7878
newtype ModuleName = ModuleName {unModuleName :: NonEmpty Name}
7979
deriving (Eq, Ord, Show, Data, Generic)
80-
deriving (FromJSON, ToJSON) via NonEmpty Name
80+
deriving (ToJSON) via NonEmpty Name
8181
deriving anyclass (NFData)
8282

8383
-- | Helper function for simple (non-hierarchical) module names.
@@ -103,7 +103,7 @@ data GlobalName (k :: GlobalNameKind) = GlobalName
103103
, baseName :: Name
104104
}
105105
deriving (Eq, Ord, Generic, Data, Show)
106-
deriving (FromJSON, ToJSON) via PrimerJSON (GlobalName k)
106+
deriving (ToJSON) via PrimerJSON (GlobalName k)
107107
deriving anyclass (NFData)
108108

109109
-- | Construct a name from a Text. This is called unsafe because there are no
@@ -129,7 +129,7 @@ data LocalNameKind
129129
newtype LocalName (k :: LocalNameKind) = LocalName {unLocalName :: Name}
130130
deriving (Eq, Ord, Show, Data, Generic)
131131
deriving (IsString) via Name
132-
deriving (FromJSON, ToJSON) via Name
132+
deriving (ToJSON) via Name
133133
deriving anyclass (NFData)
134134

135135
unsafeMkLocalName :: Text -> LocalName k
@@ -143,7 +143,7 @@ data TmVarRef
143143
= GlobalVarRef GVarName
144144
| LocalVarRef LVarName
145145
deriving (Eq, Show, Data, Generic)
146-
deriving (FromJSON, ToJSON) via PrimerJSON TmVarRef
146+
deriving (ToJSON) via PrimerJSON TmVarRef
147147
deriving anyclass (NFData)
148148

149149
-- | A class for types which have an ID.

primer/src/Primer/Core/Type.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,7 @@ data Type' a
5959
(Type' a)
6060
-- ^ body of the let; binding scopes over this
6161
deriving (Eq, Show, Data, Generic)
62-
deriving (FromJSON, ToJSON) via PrimerJSON (Type' a)
62+
deriving (ToJSON) via PrimerJSON (Type' a)
6363
deriving anyclass (NFData)
6464

6565
-- | A traversal over the metadata of a type

primer/src/Primer/Def.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,6 @@ import Primer.Core (
2121
import Primer.Core.Utils (forgetTypeMetadata)
2222
import Primer.JSON (
2323
CustomJSON (CustomJSON),
24-
FromJSON,
2524
PrimerJSON,
2625
ToJSON,
2726
)
@@ -31,7 +30,7 @@ data Def
3130
= DefPrim PrimDef
3231
| DefAST ASTDef
3332
deriving (Eq, Show, Data, Generic)
34-
deriving (FromJSON, ToJSON) via PrimerJSON Def
33+
deriving (ToJSON) via PrimerJSON Def
3534
deriving anyclass (NFData)
3635

3736
defType :: Def -> Type' ()
@@ -48,7 +47,7 @@ data ASTDef = ASTDef
4847
, astDefType :: Type
4948
}
5049
deriving (Eq, Show, Data, Generic)
51-
deriving (FromJSON, ToJSON) via PrimerJSON ASTDef
50+
deriving (ToJSON) via PrimerJSON ASTDef
5251
deriving anyclass (NFData)
5352

5453
defAST :: Def -> Maybe ASTDef

primer/src/Primer/Eval/Ann.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ import Primer.Core (
88
Expr,
99
ID,
1010
)
11-
import Primer.JSON (CustomJSON (CustomJSON), FromJSON, PrimerJSON, ToJSON)
11+
import Primer.JSON (CustomJSON (CustomJSON), PrimerJSON, ToJSON)
1212

1313
data RemoveAnnDetail = RemoveAnnDetail
1414
{ before :: Expr
@@ -19,4 +19,4 @@ data RemoveAnnDetail = RemoveAnnDetail
1919
-- ^ the ID of the type annotation
2020
}
2121
deriving (Eq, Show, Generic)
22-
deriving (FromJSON, ToJSON) via PrimerJSON RemoveAnnDetail
22+
deriving (ToJSON) via PrimerJSON RemoveAnnDetail

primer/src/Primer/Eval/Beta.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ import Primer.Core (
99
ID,
1010
LocalName,
1111
)
12-
import Primer.JSON (CustomJSON (CustomJSON), FromJSON, PrimerJSON, ToJSON)
12+
import Primer.JSON (CustomJSON (CustomJSON), PrimerJSON, ToJSON)
1313

1414
-- | Detailed information about a beta reduction (of a λ or Λ).
1515
-- If λ:
@@ -33,4 +33,4 @@ data BetaReductionDetail k domain codomain = BetaReductionDetail
3333
, types :: (domain, codomain)
3434
}
3535
deriving (Eq, Show, Generic)
36-
deriving (FromJSON, ToJSON) via PrimerJSON (BetaReductionDetail k domain codomain)
36+
deriving (ToJSON) via PrimerJSON (BetaReductionDetail k domain codomain)

primer/src/Primer/Eval/Bind.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ import Foreword
77
import Primer.Core (
88
ID,
99
)
10-
import Primer.JSON (CustomJSON (CustomJSON), FromJSON, PrimerJSON, ToJSON)
10+
import Primer.JSON (CustomJSON (CustomJSON), PrimerJSON, ToJSON)
1111
import Primer.Name (Name)
1212

1313
-- | Detailed information about a renaming of a binding.
@@ -39,4 +39,4 @@ data BindRenameDetail t = BindRenameDetail
3939
-- ^ the right hand side of the binders
4040
}
4141
deriving (Eq, Show, Generic)
42-
deriving (FromJSON, ToJSON) via PrimerJSON (BindRenameDetail t)
42+
deriving (ToJSON) via PrimerJSON (BindRenameDetail t)

primer/src/Primer/Eval/Case.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ import Primer.Core (
99
ID,
1010
ValConName,
1111
)
12-
import Primer.JSON (CustomJSON (CustomJSON), FromJSON, PrimerJSON, ToJSON)
12+
import Primer.JSON (CustomJSON (CustomJSON), PrimerJSON, ToJSON)
1313

1414
data CaseReductionDetail = CaseReductionDetail
1515
{ before :: Expr
@@ -32,4 +32,4 @@ data CaseReductionDetail = CaseReductionDetail
3232
-- ^ the let expressions binding each argument in the result
3333
}
3434
deriving (Eq, Show, Generic)
35-
deriving (FromJSON, ToJSON) via PrimerJSON CaseReductionDetail
35+
deriving (ToJSON) via PrimerJSON CaseReductionDetail

primer/src/Primer/Eval/Detail.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ import Primer.Eval.Case as Case
2323
import Primer.Eval.Inline as Inline
2424
import Primer.Eval.Let as Let
2525
import Primer.Eval.Prim as Prim
26-
import Primer.JSON (CustomJSON (CustomJSON), FromJSON, PrimerJSON, ToJSON)
26+
import Primer.JSON (CustomJSON (CustomJSON), PrimerJSON, ToJSON)
2727

2828
-- | Detailed information about a reduction step
2929
data EvalDetail
@@ -52,4 +52,4 @@ data EvalDetail
5252
| -- | Apply a primitive function
5353
ApplyPrimFun ApplyPrimFunDetail
5454
deriving (Eq, Show, Generic)
55-
deriving (FromJSON, ToJSON) via PrimerJSON EvalDetail
55+
deriving (ToJSON) via PrimerJSON EvalDetail

primer/src/Primer/Eval/Inline.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ import Primer.Core (
1313
LocalName,
1414
)
1515
import Primer.Def (ASTDef)
16-
import Primer.JSON (CustomJSON (CustomJSON), FromJSON, PrimerJSON, ToJSON)
16+
import Primer.JSON (CustomJSON (CustomJSON), PrimerJSON, ToJSON)
1717

1818
data LocalVarInlineDetail k = LocalVarInlineDetail
1919
{ letID :: ID
@@ -31,7 +31,7 @@ data LocalVarInlineDetail k = LocalVarInlineDetail
3131
-- Otherwise it is a term variable.
3232
}
3333
deriving (Eq, Show, Generic)
34-
deriving (FromJSON, ToJSON) via PrimerJSON (LocalVarInlineDetail k)
34+
deriving (ToJSON) via PrimerJSON (LocalVarInlineDetail k)
3535

3636
data GlobalVarInlineDetail = GlobalVarInlineDetail
3737
{ def :: ASTDef
@@ -42,4 +42,4 @@ data GlobalVarInlineDetail = GlobalVarInlineDetail
4242
-- ^ The result of the reduction
4343
}
4444
deriving (Eq, Show, Generic)
45-
deriving (FromJSON, ToJSON) via PrimerJSON GlobalVarInlineDetail
45+
deriving (ToJSON) via PrimerJSON GlobalVarInlineDetail

0 commit comments

Comments
 (0)