@@ -47,17 +47,30 @@ import Text.Megaparsec.Pos ( SourcePos(..) )
4747import Text.Read.Deriving
4848import Text.Show.Deriving
4949
50- -- | A location in a source file
50+ -- * data type @SrcSpan@ - a zone in a source file
51+
52+ -- | Demarcation of a chunk in a source file.
5153data SrcSpan = SrcSpan
5254 { spanBegin :: SourcePos
5355 , spanEnd :: SourcePos
5456 }
5557 deriving (Ord , Eq , Generic , Typeable , Data , Show , NFData , Hashable )
5658
59+ -- ** Instances
60+
61+ instance Semigroup SrcSpan where
62+ s1 <> s2 = SrcSpan ((min `on` spanBegin) s1 s2) ((max `on` spanEnd) s1 s2)
63+
64+ instance Binary SrcSpan
65+ instance ToJSON SrcSpan
66+ instance FromJSON SrcSpan
67+
5768#ifdef MIN_VERSION_serialise
5869instance Serialise SrcSpan
5970#endif
6071
72+ -- * data type @Ann@
73+
6174-- | A type constructor applied to a type along with an annotation
6275--
6376-- Intended to be used with 'Fix':
@@ -69,14 +82,30 @@ data Ann ann a = Ann
6982 deriving (Ord , Eq , Data , Generic , Generic1 , Typeable , Functor , Foldable ,
7083 Traversable , Read , Show , NFData , Hashable )
7184
72- instance Hashable ann => Hashable1 (Ann ann )
85+ type AnnF ann f = Compose (Ann ann ) f
7386
74- #ifdef MIN_VERSION_serialise
75- instance (Serialise ann , Serialise a ) => Serialise (Ann ann a )
76- #endif
87+ -- | Pattern: @Fix (Compose (Ann _ _))@.
88+ -- Fix composes units of (annotations & the annotated) into one object.
89+ -- Giving annotated expression.
90+ pattern AnnE
91+ :: forall ann (g :: * -> * )
92+ . ann
93+ -> g (Fix (Compose (Ann ann ) g ))
94+ -> Fix (Compose (Ann ann ) g )
95+ pattern AnnE ann a = Fix (Compose (Ann ann a))
96+ {-# complete AnnE #-}
97+
98+ annToAnnF :: Ann ann (f (Fix (AnnF ann f ))) -> Fix (AnnF ann f )
99+ annToAnnF (Ann ann a) = AnnE ann a
100+
101+ -- ** Instances
102+
103+ instance Hashable ann => Hashable1 (Ann ann )
77104
78105instance NFData ann => NFData1 (Ann ann )
79106
107+ instance (Binary ann , Binary a ) => Binary (Ann ann a )
108+
80109$ (deriveEq1 ''Ann)
81110$ (deriveEq2 ''Ann)
82111$ (deriveOrd1 ''Ann)
@@ -88,40 +117,32 @@ $(deriveShow2 ''Ann)
88117$ (deriveJSON1 defaultOptions ''Ann)
89118$ (deriveJSON2 defaultOptions ''Ann)
90119
91- instance Semigroup SrcSpan where
92- s1 <> s2 = SrcSpan ((min `on` spanBegin) s1 s2) ((max `on` spanEnd) s1 s2)
120+ #ifdef MIN_VERSION_serialise
121+ instance (Serialise ann , Serialise a ) => Serialise (Ann ann a )
122+ #endif
93123
94- type AnnF ann f = Compose (Ann ann ) f
124+ #ifdef MIN_VERSION_serialise
125+ instance Serialise r => Serialise (Compose (Ann SrcSpan ) NExprF r ) where
126+ encode (Compose (Ann ann a)) = encode ann <> encode a
127+ decode = (Compose . ) . Ann <$> decode <*> decode
128+ #endif
95129
96- annToAnnF :: Ann ann (f (Fix (AnnF ann f ))) -> Fix (AnnF ann f )
97- annToAnnF (Ann ann a) = AnnE ann a
130+ -- ** @NExprLoc{,F}@ - annotated Nix expression
98131
99132type NExprLocF = AnnF SrcSpan NExprF
100133
101- -- | A nix expression with source location at each subexpression.
134+ instance Binary r => Binary (NExprLocF r )
135+
136+ -- | Annotated Nix expression (each subexpression direct to its source location).
102137type NExprLoc = Fix NExprLocF
103138
104139#ifdef MIN_VERSION_serialise
105140instance Serialise NExprLoc
106141#endif
107142
108- instance Binary SrcSpan
109- instance (Binary ann , Binary a ) => Binary (Ann ann a )
110- instance Binary r => Binary (NExprLocF r )
111143instance Binary NExprLoc
112144
113- instance ToJSON SrcSpan
114- instance FromJSON SrcSpan
115-
116- #ifdef MIN_VERSION_serialise
117- instance Serialise r => Serialise (Compose (Ann SrcSpan ) NExprF r ) where
118- encode (Compose (Ann ann a)) = encode ann <> encode a
119- decode = (Compose . ) . Ann <$> decode <*> decode
120- #endif
121-
122- pattern AnnE :: forall ann (g :: * -> * ). ann
123- -> g (Fix (Compose (Ann ann) g)) -> Fix (Compose (Ann ann) g)
124- pattern AnnE ann a = Fix (Compose (Ann ann a))
145+ -- * Other
125146
126147stripAnnotation :: Functor f => Fix (AnnF ann f ) -> Fix f
127148stripAnnotation = unfoldFix (annotated . getCompose . unFix)
@@ -131,33 +152,32 @@ stripAnn = annotated . getCompose
131152
132153nUnary :: Ann SrcSpan NUnaryOp -> NExprLoc -> NExprLoc
133154nUnary (Ann s1 u) e1@ (AnnE s2 _) = AnnE (s1 <> s2) $ NUnary u e1
134- nUnary _ _ = error " nUnary: unexpected"
135155{-# inline nUnary #-}
136156
137157nBinary :: Ann SrcSpan NBinaryOp -> NExprLoc -> NExprLoc -> NExprLoc
138158nBinary (Ann s1 b) e1@ (AnnE s2 _) e2@ (AnnE s3 _) =
139159 AnnE (s1 <> s2 <> s3) $ NBinary b e1 e2
140- nBinary _ _ _ = error " nBinary: unexpected"
141160
142161nSelectLoc
143162 :: NExprLoc -> Ann SrcSpan (NAttrPath NExprLoc ) -> Maybe NExprLoc -> NExprLoc
144- nSelectLoc e1@ (AnnE s1 _) (Ann s2 ats) d = case d of
145- Nothing -> AnnE (s1 <> s2) $ NSelect e1 ats Nothing
146- Just e2@ (AnnE s3 _) -> AnnE (s1 <> s2 <> s3) $ NSelect e1 ats $ pure e2
147- _ -> error " nSelectLoc: unexpected"
148- nSelectLoc _ _ _ = error " nSelectLoc: unexpected"
163+ nSelectLoc e1@ (AnnE s1 _) (Ann s2 ats) =
164+ -- 2021-05-16: NOTE: This could been rewritten into function application of @(s3, pure e2)@
165+ -- if @SrcSpan@ was Monoid, which requires @SorcePos@ to be a Monoid, and upstream code prevents it.
166+ -- Question upstream: https://github.com/mrkkrp/megaparsec/issues/450
167+ maybe
168+ ( AnnE s1s2 $ NSelect e1 ats Nothing )
169+ (\ e2@ (AnnE s3 _) -> AnnE (s1s2 <> s3) $ NSelect e1 ats $ pure e2)
170+ where
171+ s1s2 = s1 <> s2
149172
150173nHasAttr :: NExprLoc -> Ann SrcSpan (NAttrPath NExprLoc ) -> NExprLoc
151174nHasAttr e1@ (AnnE s1 _) (Ann s2 ats) = AnnE (s1 <> s2) $ NHasAttr e1 ats
152- nHasAttr _ _ = error " nHasAttr: unexpected"
153175
154176nApp :: NExprLoc -> NExprLoc -> NExprLoc
155177nApp e1@ (AnnE s1 _) e2@ (AnnE s2 _) = AnnE (s1 <> s2) $ NBinary NApp e1 e2
156- nApp _ _ = error " nApp: unexpected"
157178
158179nAbs :: Ann SrcSpan (Params NExprLoc ) -> NExprLoc -> NExprLoc
159180nAbs (Ann s1 ps) e1@ (AnnE s2 _) = AnnE (s1 <> s2) $ NAbs ps e1
160- nAbs _ _ = error " nAbs: unexpected"
161181
162182nStr :: Ann SrcSpan (NString NExprLoc ) -> NExprLoc
163183nStr (Ann s1 s) = AnnE s1 $ NStr s
@@ -175,18 +195,15 @@ nullSpan = SrcSpan nullPos nullPos
175195
176196-- | Pattern systems for matching on NExprLocF constructions.
177197
178- pattern NSym_ :: SrcSpan -> VarName -> NExprLocF r
179- pattern NSym_ ann x = Compose (Ann ann (NSym x))
180-
181- pattern NSynHole_ :: SrcSpan -> Text -> NExprLocF r
182- pattern NSynHole_ ann x = Compose (Ann ann (NSynHole x))
183-
184198pattern NConstant_ :: SrcSpan -> NAtom -> NExprLocF r
185199pattern NConstant_ ann x = Compose (Ann ann (NConstant x))
186200
187201pattern NStr_ :: SrcSpan -> NString r -> NExprLocF r
188202pattern NStr_ ann x = Compose (Ann ann (NStr x))
189203
204+ pattern NSym_ :: SrcSpan -> VarName -> NExprLocF r
205+ pattern NSym_ ann x = Compose (Ann ann (NSym x))
206+
190207pattern NList_ :: SrcSpan -> [r ] -> NExprLocF r
191208pattern NList_ ann x = Compose (Ann ann (NList x))
192209
@@ -199,6 +216,12 @@ pattern NLiteralPath_ ann x = Compose (Ann ann (NLiteralPath x))
199216pattern NEnvPath_ :: SrcSpan -> FilePath -> NExprLocF r
200217pattern NEnvPath_ ann x = Compose (Ann ann (NEnvPath x))
201218
219+ pattern NUnary_ :: SrcSpan -> NUnaryOp -> r -> NExprLocF r
220+ pattern NUnary_ ann op x = Compose (Ann ann (NUnary op x))
221+
222+ pattern NBinary_ :: SrcSpan -> NBinaryOp -> r -> r -> NExprLocF r
223+ pattern NBinary_ ann op x y = Compose (Ann ann (NBinary op x y))
224+
202225pattern NSelect_ :: SrcSpan -> r -> NAttrPath r -> Maybe r -> NExprLocF r
203226pattern NSelect_ ann x p v = Compose (Ann ann (NSelect x p v))
204227
@@ -220,8 +243,6 @@ pattern NWith_ ann x y = Compose (Ann ann (NWith x y))
220243pattern NAssert_ :: SrcSpan -> r -> r -> NExprLocF r
221244pattern NAssert_ ann x y = Compose (Ann ann (NAssert x y))
222245
223- pattern NUnary_ :: SrcSpan -> NUnaryOp -> r -> NExprLocF r
224- pattern NUnary_ ann op x = Compose (Ann ann (NUnary op x))
225-
226- pattern NBinary_ :: SrcSpan -> NBinaryOp -> r -> r -> NExprLocF r
227- pattern NBinary_ ann op x y = Compose (Ann ann (NBinary op x y))
246+ pattern NSynHole_ :: SrcSpan -> Text -> NExprLocF r
247+ pattern NSynHole_ ann x = Compose (Ann ann (NSynHole x))
248+ {-# complete NConstant_, NStr_, NSym_, NList_, NSet_, NLiteralPath_, NEnvPath_, NUnary_, NBinary_, NSelect_, NHasAttr_, NAbs_, NLet_, NIf_, NWith_, NAssert_, NSynHole_ #-}
0 commit comments