1{-# LANGUAGE CPP #-} 2 3{-| Some common syntactic entities are defined in this module. 4-} 5module Agda.Syntax.Common where 6 7import Prelude hiding (null) 8 9import Control.DeepSeq 10import Control.Arrow ((&&&)) 11import Control.Applicative ((<|>), liftA2) 12 13#if __GLASGOW_HASKELL__ < 804 14import Data.Semigroup hiding (Arg) 15#endif 16import Data.Bifunctor 17import Data.ByteString.Char8 (ByteString) 18import qualified Data.ByteString.Char8 as ByteString 19import qualified Data.Foldable as Fold 20import Data.Function 21import Data.Hashable (Hashable(..)) 22import qualified Data.Strict.Maybe as Strict 23import Data.Data (Data) 24import Data.Word 25import Data.IntSet (IntSet) 26import qualified Data.IntSet as IntSet 27 28import GHC.Generics (Generic) 29 30import Agda.Syntax.Position 31 32import Agda.Utils.Functor 33import Agda.Utils.Lens 34import Agda.Utils.List1 ( List1, pattern (:|), (<|) ) 35import qualified Agda.Utils.List1 as List1 36import Agda.Utils.Maybe 37import Agda.Utils.Null 38import Agda.Utils.PartialOrd 39import Agda.Utils.POMonoid 40import Agda.Utils.Pretty 41 42import Agda.Utils.Impossible 43 44type Nat = Int 45type Arity = Nat 46 47--------------------------------------------------------------------------- 48-- * Delayed 49--------------------------------------------------------------------------- 50 51-- | Used to specify whether something should be delayed. 52data Delayed = Delayed | NotDelayed 53 deriving (Data, Show, Eq, Ord, Generic) 54 55instance KillRange Delayed where 56 killRange = id 57 58instance NFData Delayed 59 60--------------------------------------------------------------------------- 61-- * File 62--------------------------------------------------------------------------- 63 64data FileType = AgdaFileType | MdFileType | RstFileType | TexFileType | OrgFileType 65 deriving (Data, Eq, Ord, Show, Generic) 66 67instance Pretty FileType where 68 pretty = \case 69 AgdaFileType -> "Agda" 70 MdFileType -> "Markdown" 71 RstFileType -> "ReStructedText" 72 TexFileType -> "LaTeX" 73 OrgFileType -> "org-mode" 74 75instance NFData FileType 76 77--------------------------------------------------------------------------- 78-- * Record Directives 79--------------------------------------------------------------------------- 80 81data RecordDirectives' a = RecordDirectives 82 { recInductive :: Maybe (Ranged Induction) 83 , recHasEta :: Maybe HasEta0 84 , recPattern :: Maybe Range 85 , recConstructor :: Maybe a 86 } deriving (Functor, Data, Show, Eq) 87 88emptyRecordDirectives :: RecordDirectives' a 89emptyRecordDirectives = RecordDirectives empty empty empty empty 90 91instance HasRange a => HasRange (RecordDirectives' a) where 92 getRange (RecordDirectives a b c d) = getRange (a,b,c,d) 93 94instance KillRange a => KillRange (RecordDirectives' a) where 95 killRange (RecordDirectives a b c d) = killRange4 RecordDirectives a b c d 96 97instance NFData a => NFData (RecordDirectives' a) where 98 rnf (RecordDirectives a b c d) = c `seq` rnf (a, b, d) 99 100--------------------------------------------------------------------------- 101-- * Eta-equality 102--------------------------------------------------------------------------- 103 104-- | Does a record come with eta-equality? 105data HasEta' a 106 = YesEta 107 | NoEta a 108 deriving (Data, Show, Eq, Ord, Functor, Foldable, Traversable) 109 110instance HasRange a => HasRange (HasEta' a) where 111 getRange = foldMap getRange 112 113instance KillRange a => KillRange (HasEta' a) where 114 killRange = fmap killRange 115 116instance NFData a => NFData (HasEta' a) where 117 rnf YesEta = () 118 rnf (NoEta p) = rnf p 119 120-- | Pattern and copattern matching is allowed in the presence of eta. 121-- 122-- In the absence of eta, we have to choose whether we want to allow 123-- matching on the constructor or copattern matching with the projections. 124-- Having both leads to breakage of subject reduction (issue #4560). 125 126type HasEta = HasEta' PatternOrCopattern 127type HasEta0 = HasEta' () 128 129-- | For a record without eta, which type of matching do we allow? 130data PatternOrCopattern 131 = PatternMatching 132 -- ^ Can match on the record constructor. 133 | CopatternMatching 134 -- ^ Can copattern match using the projections. (Default.) 135 deriving (Data, Show, Eq, Ord, Enum, Bounded) 136 137instance NFData PatternOrCopattern where 138 rnf PatternMatching = () 139 rnf CopatternMatching = () 140 141instance HasRange PatternOrCopattern where 142 getRange _ = noRange 143 144instance KillRange PatternOrCopattern where 145 killRange = id 146 147-- | Can we pattern match on the record constructor? 148class PatternMatchingAllowed a where 149 patternMatchingAllowed :: a -> Bool 150 151instance PatternMatchingAllowed PatternOrCopattern where 152 patternMatchingAllowed = (== PatternMatching) 153 154instance PatternMatchingAllowed HasEta where 155 patternMatchingAllowed = \case 156 YesEta -> True 157 NoEta p -> patternMatchingAllowed p 158 159 160-- | Can we construct a record by copattern matching? 161class CopatternMatchingAllowed a where 162 copatternMatchingAllowed :: a -> Bool 163 164instance CopatternMatchingAllowed PatternOrCopattern where 165 copatternMatchingAllowed = (== CopatternMatching) 166 167instance CopatternMatchingAllowed HasEta where 168 copatternMatchingAllowed = \case 169 YesEta -> True 170 NoEta p -> copatternMatchingAllowed p 171 172--------------------------------------------------------------------------- 173-- * Induction 174--------------------------------------------------------------------------- 175 176-- | @Inductive < Coinductive@ 177data Induction = Inductive | CoInductive -- Keep in this order! 178 deriving (Data, Eq, Ord, Show) 179 180instance Pretty Induction where 181 pretty Inductive = "inductive" 182 pretty CoInductive = "coinductive" 183 184instance HasRange Induction where 185 getRange _ = noRange 186 187instance KillRange Induction where 188 killRange = id 189 190instance NFData Induction where 191 rnf Inductive = () 192 rnf CoInductive = () 193 194instance PatternMatchingAllowed Induction where 195 patternMatchingAllowed = (== Inductive) 196 197--------------------------------------------------------------------------- 198-- * Hiding 199--------------------------------------------------------------------------- 200 201data Overlappable = YesOverlap | NoOverlap 202 deriving (Data, Show, Eq, Ord) 203 204data Hiding = Hidden | Instance Overlappable | NotHidden 205 deriving (Data, Show, Eq, Ord) 206 207instance Pretty Hiding where 208 pretty = \case 209 Hidden -> "hidden" 210 NotHidden -> "visible" 211 Instance{} -> "instance" 212 213-- | Just for the 'Hiding' instance. Should never combine different 214-- overlapping. 215instance Semigroup Overlappable where 216 NoOverlap <> NoOverlap = NoOverlap 217 YesOverlap <> YesOverlap = YesOverlap 218 _ <> _ = __IMPOSSIBLE__ 219 220-- | 'Hiding' is an idempotent partial monoid, with unit 'NotHidden'. 221-- 'Instance' and 'NotHidden' are incompatible. 222instance Semigroup Hiding where 223 NotHidden <> h = h 224 h <> NotHidden = h 225 Hidden <> Hidden = Hidden 226 Instance o <> Instance o' = Instance (o <> o') 227 _ <> _ = __IMPOSSIBLE__ 228 229instance Monoid Overlappable where 230 mempty = NoOverlap 231 mappend = (<>) 232 233instance Monoid Hiding where 234 mempty = NotHidden 235 mappend = (<>) 236 237instance HasRange Hiding where 238 getRange _ = noRange 239 240instance KillRange Hiding where 241 killRange = id 242 243instance NFData Overlappable where 244 rnf NoOverlap = () 245 rnf YesOverlap = () 246 247instance NFData Hiding where 248 rnf Hidden = () 249 rnf (Instance o) = rnf o 250 rnf NotHidden = () 251 252-- | Decorating something with 'Hiding' information. 253data WithHiding a = WithHiding 254 { whHiding :: !Hiding 255 , whThing :: a 256 } 257 deriving (Data, Eq, Ord, Show, Functor, Foldable, Traversable) 258 259instance Decoration WithHiding where 260 traverseF f (WithHiding h a) = WithHiding h <$> f a 261 262instance Applicative WithHiding where 263 pure = WithHiding mempty 264 WithHiding h f <*> WithHiding h' a = WithHiding (mappend h h') (f a) 265 266instance HasRange a => HasRange (WithHiding a) where 267 getRange = getRange . dget 268 269instance SetRange a => SetRange (WithHiding a) where 270 setRange = fmap . setRange 271 272instance KillRange a => KillRange (WithHiding a) where 273 killRange = fmap killRange 274 275instance NFData a => NFData (WithHiding a) where 276 rnf (WithHiding _ a) = rnf a 277 278-- | A lens to access the 'Hiding' attribute in data structures. 279-- Minimal implementation: @getHiding@ and @mapHiding@ or @LensArgInfo@. 280class LensHiding a where 281 282 getHiding :: a -> Hiding 283 284 setHiding :: Hiding -> a -> a 285 setHiding h = mapHiding (const h) 286 287 mapHiding :: (Hiding -> Hiding) -> a -> a 288 289 default getHiding :: LensArgInfo a => a -> Hiding 290 getHiding = argInfoHiding . getArgInfo 291 292 default mapHiding :: LensArgInfo a => (Hiding -> Hiding) -> a -> a 293 mapHiding f = mapArgInfo $ \ ai -> ai { argInfoHiding = f $ argInfoHiding ai } 294 295instance LensHiding Hiding where 296 getHiding = id 297 setHiding = const 298 mapHiding = id 299 300instance LensHiding (WithHiding a) where 301 getHiding (WithHiding h _) = h 302 setHiding h (WithHiding _ a) = WithHiding h a 303 mapHiding f (WithHiding h a) = WithHiding (f h) a 304 305instance LensHiding a => LensHiding (Named nm a) where 306 getHiding = getHiding . namedThing 307 setHiding = fmap . setHiding 308 mapHiding = fmap . mapHiding 309 310-- | Monoidal composition of 'Hiding' information in some data. 311mergeHiding :: LensHiding a => WithHiding a -> a 312mergeHiding (WithHiding h a) = mapHiding (mappend h) a 313 314-- | 'NotHidden' arguments are @visible@. 315visible :: LensHiding a => a -> Bool 316visible a = getHiding a == NotHidden 317 318-- | 'Instance' and 'Hidden' arguments are @notVisible@. 319notVisible :: LensHiding a => a -> Bool 320notVisible a = getHiding a /= NotHidden 321 322-- | 'Hidden' arguments are @hidden@. 323hidden :: LensHiding a => a -> Bool 324hidden a = getHiding a == Hidden 325 326hide :: LensHiding a => a -> a 327hide = setHiding Hidden 328 329hideOrKeepInstance :: LensHiding a => a -> a 330hideOrKeepInstance x = 331 case getHiding x of 332 Hidden -> x 333 Instance{} -> x 334 NotHidden -> setHiding Hidden x 335 336makeInstance :: LensHiding a => a -> a 337makeInstance = makeInstance' NoOverlap 338 339makeInstance' :: LensHiding a => Overlappable -> a -> a 340makeInstance' o = setHiding (Instance o) 341 342isOverlappable :: LensHiding a => a -> Bool 343isOverlappable x = 344 case getHiding x of 345 Instance YesOverlap -> True 346 _ -> False 347 348isInstance :: LensHiding a => a -> Bool 349isInstance x = 350 case getHiding x of 351 Instance{} -> True 352 _ -> False 353 354-- | Ignores 'Overlappable'. 355sameHiding :: (LensHiding a, LensHiding b) => a -> b -> Bool 356sameHiding x y = 357 case (getHiding x, getHiding y) of 358 (Instance{}, Instance{}) -> True 359 (hx, hy) -> hx == hy 360 361--------------------------------------------------------------------------- 362-- * Modalities 363--------------------------------------------------------------------------- 364 365-- | Type wrapper to indicate additive monoid/semigroup context. 366newtype UnderAddition t = UnderAddition t deriving (Show, Functor, Eq, Ord, PartialOrd) 367 368instance Applicative UnderAddition where 369 pure = UnderAddition 370 (<*>) (UnderAddition f) (UnderAddition a) = pure (f a) 371 372-- | Type wrapper to indicate composition or multiplicative monoid/semigroup context. 373newtype UnderComposition t = UnderComposition t deriving (Show, Functor, Eq, Ord, PartialOrd) 374 375instance Applicative UnderComposition where 376 pure = UnderComposition 377 (<*>) (UnderComposition f) (UnderComposition a) = pure (f a) 378 379-- | We have a tuple of modalities, which might not be fully orthogonal. 380-- For instance, irrelevant stuff is also run-time irrelevant. 381data Modality = Modality 382 { modRelevance :: Relevance 383 -- ^ Legacy irrelevance. 384 -- See Pfenning, LiCS 2001; Abel/Vezzosi/Winterhalter, ICFP 2017. 385 , modQuantity :: Quantity 386 -- ^ Cardinality / runtime erasure. 387 -- See Conor McBride, I got plenty o' nutting, Wadlerfest 2016. 388 -- See Bob Atkey, Syntax and Semantics of Quantitative Type Theory, LiCS 2018. 389 , modCohesion :: Cohesion 390 -- ^ Cohesion/what was in Agda-flat. 391 -- see "Brouwer's fixed-point theorem in real-cohesive homotopy type theory" (arXiv:1509.07584) 392 -- Currently only the comonad is implemented. 393 } deriving (Data, Eq, Ord, Show, Generic) 394 395-- | Dominance ordering. 396instance PartialOrd Modality where 397 comparable (Modality r q c) (Modality r' q' c') = comparable (r, (q, c)) (r', (q', c')) 398 399-- | Pointwise composition. 400instance Semigroup (UnderComposition Modality) where 401 (<>) = liftA2 composeModality 402 403-- | Pointwise composition unit. 404instance Monoid (UnderComposition Modality) where 405 mempty = pure unitModality 406 mappend = (<>) 407 408instance POSemigroup (UnderComposition Modality) where 409instance POMonoid (UnderComposition Modality) where 410 411instance LeftClosedPOMonoid (UnderComposition Modality) where 412 inverseCompose = liftA2 inverseComposeModality 413 414-- | Pointwise addition. 415instance Semigroup (UnderAddition Modality) where 416 (<>) = liftA2 addModality 417 418-- | Pointwise additive unit. 419instance Monoid (UnderAddition Modality) where 420 mempty = pure zeroModality 421 mappend = (<>) 422 423instance POSemigroup (UnderAddition Modality) where 424instance POMonoid (UnderAddition Modality) where 425 426-- | @m `moreUsableModality` m'@ means that an @m@ can be used 427-- where ever an @m'@ is required. 428 429moreUsableModality :: Modality -> Modality -> Bool 430moreUsableModality m m' = related m POLE m' 431 432usableModality :: LensModality a => a -> Bool 433usableModality a = usableRelevance m && usableQuantity m 434 where m = getModality a 435 436-- | Multiplicative monoid (standard monoid). 437composeModality :: Modality -> Modality -> Modality 438composeModality (Modality r q c) (Modality r' q' c') = 439 Modality (r `composeRelevance` r') 440 (q `composeQuantity` q') 441 (c `composeCohesion` c') 442 443-- | Compose with modality flag from the left. 444-- This function is e.g. used to update the modality information 445-- on pattern variables @a@ after a match against something of modality @q@. 446applyModality :: LensModality a => Modality -> a -> a 447applyModality m = mapModality (m `composeModality`) 448 449-- | @inverseComposeModality r x@ returns the least modality @y@ 450-- such that forall @x@, @y@ we have 451-- @x \`moreUsableModality\` (r \`composeModality\` y)@ 452-- iff 453-- @(r \`inverseComposeModality\` x) \`moreUsableModality\` y@ (Galois connection). 454inverseComposeModality :: Modality -> Modality -> Modality 455inverseComposeModality (Modality r q c) (Modality r' q' c') = 456 Modality (r `inverseComposeRelevance` r') 457 (q `inverseComposeQuantity` q') 458 (c `inverseComposeCohesion` c') 459 460-- | Left division by a 'Modality'. 461-- Used e.g. to modify context when going into a @m@ argument. 462-- 463-- Note that this function does not change quantities. 464inverseApplyModalityButNotQuantity :: LensModality a => Modality -> a -> a 465inverseApplyModalityButNotQuantity m = 466 mapModality (m' `inverseComposeModality`) 467 where 468 m' = setQuantity (Quantity1 Q1Inferred) m 469 470-- | 'Modality' forms a pointwise additive monoid. 471addModality :: Modality -> Modality -> Modality 472addModality (Modality r q c) (Modality r' q' c') = Modality (addRelevance r r') (addQuantity q q') (addCohesion c c') 473 474-- | Identity under addition 475zeroModality :: Modality 476zeroModality = Modality zeroRelevance zeroQuantity zeroCohesion 477 478-- | Identity under composition 479unitModality :: Modality 480unitModality = Modality unitRelevance unitQuantity unitCohesion 481 482-- | Absorptive element under addition. 483topModality :: Modality 484topModality = Modality topRelevance topQuantity topCohesion 485 486-- | The default Modality 487-- Beware that this is neither the additive unit nor the unit under 488-- composition, because the default quantity is ω. 489defaultModality :: Modality 490defaultModality = Modality defaultRelevance defaultQuantity defaultCohesion 491 492-- | Equality ignoring origin. 493 494sameModality :: (LensModality a, LensModality b) => a -> b -> Bool 495sameModality x y = case (getModality x , getModality y) of 496 (Modality r q c , Modality r' q' c') -> sameRelevance r r' && sameQuantity q q' && sameCohesion c c' 497 498-- boilerplate instances 499 500instance HasRange Modality where 501 getRange (Modality r q c) = getRange (r, q, c) 502 503instance KillRange Modality where 504 killRange (Modality r q c) = killRange3 Modality r q c 505 506instance NFData Modality where 507 508-- Lens stuff 509 510lModRelevance :: Lens' Relevance Modality 511lModRelevance f m = f (modRelevance m) <&> \ r -> m { modRelevance = r } 512 513lModQuantity :: Lens' Quantity Modality 514lModQuantity f m = f (modQuantity m) <&> \ q -> m { modQuantity = q } 515 516lModCohesion :: Lens' Cohesion Modality 517lModCohesion f m = f (modCohesion m) <&> \ q -> m { modCohesion = q } 518 519class LensModality a where 520 521 getModality :: a -> Modality 522 523 setModality :: Modality -> a -> a 524 setModality = mapModality . const 525 526 mapModality :: (Modality -> Modality) -> a -> a 527 528 default getModality :: LensArgInfo a => a -> Modality 529 getModality = argInfoModality . getArgInfo 530 531 default mapModality :: LensArgInfo a => (Modality -> Modality) -> a -> a 532 mapModality f = mapArgInfo $ \ ai -> ai { argInfoModality = f $ argInfoModality ai } 533 534instance LensModality Modality where 535 getModality = id 536 setModality = const 537 mapModality = id 538 539instance LensRelevance Modality where 540 getRelevance = modRelevance 541 setRelevance h m = m { modRelevance = h } 542 mapRelevance f m = m { modRelevance = f (modRelevance m) } 543 544instance LensQuantity Modality where 545 getQuantity = modQuantity 546 setQuantity h m = m { modQuantity = h } 547 mapQuantity f m = m { modQuantity = f (modQuantity m) } 548 549instance LensCohesion Modality where 550 getCohesion = modCohesion 551 setCohesion h m = m { modCohesion = h } 552 mapCohesion f m = m { modCohesion = f (modCohesion m) } 553 554-- default accessors for Relevance 555 556getRelevanceMod :: LensModality a => LensGet Relevance a 557getRelevanceMod = getRelevance . getModality 558 559setRelevanceMod :: LensModality a => LensSet Relevance a 560setRelevanceMod = mapModality . setRelevance 561 562mapRelevanceMod :: LensModality a => LensMap Relevance a 563mapRelevanceMod = mapModality . mapRelevance 564 565-- default accessors for Quantity 566 567getQuantityMod :: LensModality a => LensGet Quantity a 568getQuantityMod = getQuantity . getModality 569 570setQuantityMod :: LensModality a => LensSet Quantity a 571setQuantityMod = mapModality . setQuantity 572 573mapQuantityMod :: LensModality a => LensMap Quantity a 574mapQuantityMod = mapModality . mapQuantity 575 576-- default accessors for Cohesion 577 578getCohesionMod :: LensModality a => LensGet Cohesion a 579getCohesionMod = getCohesion . getModality 580 581setCohesionMod :: LensModality a => LensSet Cohesion a 582setCohesionMod = mapModality . setCohesion 583 584mapCohesionMod :: LensModality a => LensMap Cohesion a 585mapCohesionMod = mapModality . mapCohesion 586 587--------------------------------------------------------------------------- 588-- * Quantities 589--------------------------------------------------------------------------- 590 591-- ** Quantity origin. 592 593-- | Origin of 'Quantity0'. 594data Q0Origin 595 = Q0Inferred -- ^ User wrote nothing. 596 | Q0 Range -- ^ User wrote "@0". 597 | Q0Erased Range -- ^ User wrote "@erased". 598 deriving (Data, Show, Generic, Eq, Ord) 599 600-- | Origin of 'Quantity1'. 601data Q1Origin 602 = Q1Inferred -- ^ User wrote nothing. 603 | Q1 Range -- ^ User wrote "@1". 604 | Q1Linear Range -- ^ User wrote "@linear". 605 deriving (Data, Show, Generic, Eq, Ord) 606 607-- | Origin of 'Quantityω'. 608data QωOrigin 609 = QωInferred -- ^ User wrote nothing. 610 | Qω Range -- ^ User wrote "@ω". 611 | QωPlenty Range -- ^ User wrote "@plenty". 612 deriving (Data, Show, Generic, Eq, Ord) 613 614-- *** Instances for 'Q0Origin'. 615 616-- | Right-biased composition, because the left quantity 617-- acts as context, and the right one as occurrence. 618instance Semigroup Q0Origin where 619 (<>) = curry $ \case 620 (Q0Inferred, o) -> o 621 (o, Q0Inferred) -> o 622 (o, Q0 r) -> Q0 $ fuseRange o r 623 (o, Q0Erased r) -> Q0 $ fuseRange o r 624 625instance Monoid Q0Origin where 626 mempty = Q0Inferred 627 mappend = (<>) 628 629instance Null Q0Origin where 630 empty = mempty 631 632instance HasRange Q0Origin where 633 getRange = \case 634 Q0Inferred -> noRange 635 Q0 r -> r 636 Q0Erased r -> r 637 638instance SetRange Q0Origin where 639 setRange r = \case 640 Q0Inferred -> Q0Inferred 641 Q0 _ -> Q0 r 642 Q0Erased _ -> Q0Erased r 643 644instance KillRange Q0Origin where 645 killRange = \case 646 Q0Inferred -> Q0Inferred 647 Q0 _ -> Q0 noRange 648 Q0Erased _ -> Q0Erased noRange 649 650instance NFData Q0Origin where 651 rnf = \case 652 Q0Inferred -> () 653 Q0 _ -> () 654 Q0Erased _ -> () 655 656-- *** Instances for 'Q1Origin'. 657 658-- | Right-biased composition, because the left quantity 659-- acts as context, and the right one as occurrence. 660instance Semigroup Q1Origin where 661 (<>) = curry $ \case 662 (Q1Inferred, o) -> o 663 (o, Q1Inferred) -> o 664 (o, Q1 r) -> Q1 $ fuseRange o r 665 (o, Q1Linear r) -> Q1 $ fuseRange o r 666 667instance Monoid Q1Origin where 668 mempty = Q1Inferred 669 mappend = (<>) 670 671instance Null Q1Origin where 672 empty = mempty 673 674instance HasRange Q1Origin where 675 getRange = \case 676 Q1Inferred -> noRange 677 Q1 r -> r 678 Q1Linear r -> r 679 680instance SetRange Q1Origin where 681 setRange r = \case 682 Q1Inferred -> Q1Inferred 683 Q1 _ -> Q1 r 684 Q1Linear _ -> Q1Linear r 685 686instance KillRange Q1Origin where 687 killRange = \case 688 Q1Inferred -> Q1Inferred 689 Q1 _ -> Q1 noRange 690 Q1Linear _ -> Q1Linear noRange 691 692instance NFData Q1Origin where 693 rnf = \case 694 Q1Inferred -> () 695 Q1 _ -> () 696 Q1Linear _ -> () 697 698-- *** Instances for 'QωOrigin'. 699 700-- | Right-biased composition, because the left quantity 701-- acts as context, and the right one as occurrence. 702instance Semigroup QωOrigin where 703 (<>) = curry $ \case 704 (QωInferred, o) -> o 705 (o, QωInferred) -> o 706 (o, Qω r) -> Qω $ fuseRange o r 707 (o, QωPlenty r) -> Qω $ fuseRange o r 708 709instance Monoid QωOrigin where 710 mempty = QωInferred 711 mappend = (<>) 712 713instance Null QωOrigin where 714 empty = mempty 715 716instance HasRange QωOrigin where 717 getRange = \case 718 QωInferred -> noRange 719 Qω r -> r 720 QωPlenty r -> r 721 722instance SetRange QωOrigin where 723 setRange r = \case 724 QωInferred -> QωInferred 725 Qω _ -> Qω r 726 QωPlenty _ -> QωPlenty r 727 728instance KillRange QωOrigin where 729 killRange = \case 730 QωInferred -> QωInferred 731 Qω _ -> Qω noRange 732 QωPlenty _ -> QωPlenty noRange 733 734instance NFData QωOrigin where 735 rnf = \case 736 QωInferred -> () 737 Qω _ -> () 738 QωPlenty _ -> () 739 740-- ** Quantity. 741 742-- | Quantity for linearity. 743-- 744-- A quantity is a set of natural numbers, indicating possible semantic 745-- uses of a variable. A singleton set @{n}@ requires that the 746-- corresponding variable is used exactly @n@ times. 747-- 748data Quantity 749 = Quantity0 Q0Origin -- ^ Zero uses @{0}@, erased at runtime. 750 | Quantity1 Q1Origin -- ^ Linear use @{1}@ (could be updated destructively). 751 -- Mostly TODO (needs postponable constraints between quantities to compute uses). 752 | Quantityω QωOrigin -- ^ Unrestricted use @ℕ@. 753 deriving (Data, Show, Generic, Eq, Ord) 754 -- @Ord@ instance in case @Quantity@ is used in keys for maps etc. 755 756-- | Equality ignoring origin. 757 758sameQuantity :: Quantity -> Quantity -> Bool 759sameQuantity = curry $ \case 760 (Quantity0{}, Quantity0{}) -> True 761 (Quantity1{}, Quantity1{}) -> True 762 (Quantityω{}, Quantityω{}) -> True 763 _ -> False 764 765-- | Composition of quantities (multiplication). 766-- 767-- 'Quantity0' is dominant. 768-- 'Quantity1' is neutral. 769-- 770-- Right-biased for origin. 771-- 772instance Semigroup (UnderComposition Quantity) where 773 (<>) = liftA2 composeQuantity 774 775-- | In the absense of finite quantities besides 0, ω is the unit. 776-- Otherwise, 1 is the unit. 777instance Monoid (UnderComposition Quantity) where 778 mempty = pure unitQuantity 779 mappend = (<>) 780 781instance POSemigroup (UnderComposition Quantity) where 782instance POMonoid (UnderComposition Quantity) where 783 784instance LeftClosedPOMonoid (UnderComposition Quantity) where 785 inverseCompose = liftA2 inverseComposeQuantity 786 787instance Semigroup (UnderAddition Quantity) where 788 (<>) = liftA2 addQuantity 789 790instance Monoid (UnderAddition Quantity) where 791 mempty = pure zeroQuantity 792 mappend = (<>) 793 794instance POSemigroup (UnderAddition Quantity) where 795instance POMonoid (UnderAddition Quantity) where 796 797-- | Note that the order is @ω ≤ 0,1@, more options is smaller. 798instance PartialOrd Quantity where 799 comparable = curry $ \case 800 (q, q') | sameQuantity q q' -> POEQ 801 -- ω is least 802 (Quantityω{}, _) -> POLT 803 (_, Quantityω{}) -> POGT 804 -- others are uncomparable 805 _ -> POAny 806 807-- | 'Quantity' forms an additive monoid with zero Quantity0. 808addQuantity :: Quantity -> Quantity -> Quantity 809addQuantity = curry $ \case 810 -- ω is absorptive 811 (q@Quantityω{}, _) -> q 812 (_, q@Quantityω{}) -> q 813 -- 0 is neutral 814 (Quantity0{}, q) -> q 815 (q, Quantity0{}) -> q 816 -- 1 + 1 = ω 817 (Quantity1 _, Quantity1 _) -> topQuantity 818 819-- | Identity element under addition 820zeroQuantity :: Quantity 821zeroQuantity = Quantity0 mempty 822 823-- | Absorptive element! 824-- This differs from Relevance and Cohesion whose default 825-- is the multiplicative unit. 826defaultQuantity :: Quantity 827defaultQuantity = topQuantity 828 829-- | Identity element under composition 830unitQuantity :: Quantity 831unitQuantity = Quantityω mempty 832 833-- | Absorptive element is ω. 834topQuantity :: Quantity 835topQuantity = Quantityω mempty 836 837-- | @m `moreUsableQuantity` m'@ means that an @m@ can be used 838-- where ever an @m'@ is required. 839 840moreQuantity :: Quantity -> Quantity -> Bool 841moreQuantity m m' = related m POLE m' 842 843-- | Composition of quantities (multiplication). 844-- 845-- 'Quantity0' is dominant. 846-- 'Quantity1' is neutral. 847-- 848-- Right-biased for origin. 849-- 850composeQuantity :: Quantity -> Quantity -> Quantity 851composeQuantity = curry $ \case 852 (Quantity1 o, Quantity1 o') -> Quantity1 (o <> o') 853 (Quantity1{}, q ) -> q 854 (q , Quantity1{} ) -> q 855 (Quantity0 o, Quantity0 o') -> Quantity0 (o <> o') 856 (_ , Quantity0 o ) -> Quantity0 o 857 (Quantity0 o, _ ) -> Quantity0 o 858 (Quantityω o, Quantityω o') -> Quantityω (o <> o') 859 860-- | Compose with quantity flag from the left. 861-- This function is e.g. used to update the quantity information 862-- on pattern variables @a@ after a match against something of quantity @q@. 863 864applyQuantity :: LensQuantity a => Quantity -> a -> a 865applyQuantity q = mapQuantity (q `composeQuantity`) 866 867-- | @inverseComposeQuantity r x@ returns the least quantity @y@ 868-- such that forall @x@, @y@ we have 869-- @x \`moreQuantity\` (r \`composeQuantity\` y)@ 870-- iff 871-- @(r \`inverseComposeQuantity\` x) \`moreQuantity\` y@ (Galois connection). 872 873inverseComposeQuantity :: Quantity -> Quantity -> Quantity 874inverseComposeQuantity = curry $ \case 875 (Quantity1{} , x) -> x -- going to linear arg: nothing changes 876 (Quantity0{} , x) -> topQuantity -- going to erased arg: every thing usable 877 (Quantityω{} , x@Quantityω{}) -> x 878 (Quantityω{} , _) -> zeroQuantity -- linear resources are unusable as arguments to unrestricted functions 879 880-- | Left division by a 'Quantity'. 881-- Used e.g. to modify context when going into a @q@ argument. 882 883inverseApplyQuantity :: LensQuantity a => Quantity -> a -> a 884inverseApplyQuantity q = mapQuantity (q `inverseComposeQuantity`) 885 886-- | Check for 'Quantity0'. 887 888hasQuantity0 :: LensQuantity a => a -> Bool 889hasQuantity0 a 890 | Quantity0{} <- getQuantity a = True 891 | otherwise = False 892 893-- | Check for 'Quantity1'. 894 895hasQuantity1 :: LensQuantity a => a -> Bool 896hasQuantity1 a 897 | Quantity1{} <- getQuantity a = True 898 | otherwise = False 899 900-- | Check for 'Quantityω'. 901 902hasQuantityω :: LensQuantity a => a -> Bool 903hasQuantityω a 904 | Quantityω{} <- getQuantity a = True 905 | otherwise = False 906 907-- | Did the user supply a quantity annotation? 908 909noUserQuantity :: LensQuantity a => a -> Bool 910noUserQuantity a = case getQuantity a of 911 Quantity0 o -> null o 912 Quantity1 o -> null o 913 Quantityω o -> null o 914 915-- | A thing of quantity 0 is unusable, all others are usable. 916 917usableQuantity :: LensQuantity a => a -> Bool 918usableQuantity = not . hasQuantity0 919 920-- boilerplate instances 921 922class LensQuantity a where 923 924 getQuantity :: a -> Quantity 925 926 setQuantity :: Quantity -> a -> a 927 setQuantity = mapQuantity . const 928 929 mapQuantity :: (Quantity -> Quantity) -> a -> a 930 931 default getQuantity :: LensModality a => a -> Quantity 932 getQuantity = modQuantity . getModality 933 934 default mapQuantity :: LensModality a => (Quantity -> Quantity) -> a -> a 935 mapQuantity f = mapModality $ \ ai -> ai { modQuantity = f $ modQuantity ai } 936 937instance LensQuantity Quantity where 938 getQuantity = id 939 setQuantity = const 940 mapQuantity = id 941 942instance HasRange Quantity where 943 getRange = \case 944 Quantity0 o -> getRange o 945 Quantity1 o -> getRange o 946 Quantityω o -> getRange o 947 948instance SetRange Quantity where 949 setRange r = \case 950 Quantity0 o -> Quantity0 $ setRange r o 951 Quantity1 o -> Quantity1 $ setRange r o 952 Quantityω o -> Quantityω $ setRange r o 953 954instance KillRange Quantity where 955 killRange = \case 956 Quantity0 o -> Quantity0 $ killRange o 957 Quantity1 o -> Quantity1 $ killRange o 958 Quantityω o -> Quantityω $ killRange o 959 960instance NFData Quantity where 961 rnf (Quantity0 o) = rnf o 962 rnf (Quantity1 o) = rnf o 963 rnf (Quantityω o) = rnf o 964 965-- ** Erased. 966 967-- | A special case of 'Quantity': erased or not. 968 969data Erased 970 = Erased Q0Origin 971 | NotErased QωOrigin 972 deriving (Data, Show, Eq, Generic) 973 974-- | The default value of type 'Erased': not erased. 975 976defaultErased :: Erased 977defaultErased = NotErased QωInferred 978 979-- 'Erased' can be converted into 'Quantity'. 980 981asQuantity :: Erased -> Quantity 982asQuantity (Erased o) = Quantity0 o 983asQuantity (NotErased o) = Quantityω o 984 985-- | Equality ignoring origin. 986 987sameErased :: Erased -> Erased -> Bool 988sameErased = sameQuantity `on` asQuantity 989 990-- | Is the value \"erased\"? 991 992isErased :: Erased -> Bool 993isErased = hasQuantity0 . asQuantity 994 995instance NFData Erased 996 997instance HasRange Erased where 998 getRange = getRange . asQuantity 999 1000instance KillRange Erased where 1001 killRange = \case 1002 Erased o -> Erased $ killRange o 1003 NotErased o -> NotErased $ killRange o 1004 1005-- | Composition of values of type 'Erased'. 1006-- 1007-- 'Erased' is dominant. 1008-- 'NotErased' is neutral. 1009-- 1010-- Right-biased for the origin. 1011 1012composeErased :: Erased -> Erased -> Erased 1013composeErased = curry $ \case 1014 (Erased o, Erased o') -> Erased (o <> o') 1015 (NotErased _, Erased o) -> Erased o 1016 (Erased o, NotErased _) -> Erased o 1017 (NotErased o, NotErased o') -> NotErased (o <> o') 1018 1019instance Semigroup (UnderComposition Erased) where 1020 (<>) = liftA2 composeErased 1021 1022--------------------------------------------------------------------------- 1023-- * Relevance 1024--------------------------------------------------------------------------- 1025 1026-- | A function argument can be relevant or irrelevant. 1027-- See "Agda.TypeChecking.Irrelevance". 1028data Relevance 1029 = Relevant -- ^ The argument is (possibly) relevant at compile-time. 1030 | NonStrict -- ^ The argument may never flow into evaluation position. 1031 -- Therefore, it is irrelevant at run-time. 1032 -- It is treated relevantly during equality checking. 1033 | Irrelevant -- ^ The argument is irrelevant at compile- and runtime. 1034 deriving (Data, Show, Eq, Enum, Bounded, Generic) 1035 1036allRelevances :: [Relevance] 1037allRelevances = [minBound..maxBound] 1038 1039instance HasRange Relevance where 1040 getRange _ = noRange 1041 1042instance SetRange Relevance where 1043 setRange _ = id 1044 1045instance KillRange Relevance where 1046 killRange rel = rel -- no range to kill 1047 1048instance NFData Relevance where 1049 rnf Relevant = () 1050 rnf NonStrict = () 1051 rnf Irrelevant = () 1052 1053-- | A lens to access the 'Relevance' attribute in data structures. 1054-- Minimal implementation: @getRelevance@ and @mapRelevance@ or @LensModality@. 1055class LensRelevance a where 1056 1057 getRelevance :: a -> Relevance 1058 1059 setRelevance :: Relevance -> a -> a 1060 setRelevance h = mapRelevance (const h) 1061 1062 mapRelevance :: (Relevance -> Relevance) -> a -> a 1063 1064 default getRelevance :: LensModality a => a -> Relevance 1065 getRelevance = modRelevance . getModality 1066 1067 default mapRelevance :: LensModality a => (Relevance -> Relevance) -> a -> a 1068 mapRelevance f = mapModality $ \ ai -> ai { modRelevance = f $ modRelevance ai } 1069 1070instance LensRelevance Relevance where 1071 getRelevance = id 1072 setRelevance = const 1073 mapRelevance = id 1074 1075isRelevant :: LensRelevance a => a -> Bool 1076isRelevant a = getRelevance a == Relevant 1077 1078isIrrelevant :: LensRelevance a => a -> Bool 1079isIrrelevant a = getRelevance a == Irrelevant 1080 1081isNonStrict :: LensRelevance a => a -> Bool 1082isNonStrict a = getRelevance a == NonStrict 1083 1084-- | Information ordering. 1085-- @Relevant \`moreRelevant\` 1086-- NonStrict \`moreRelevant\` 1087-- Irrelevant@ 1088moreRelevant :: Relevance -> Relevance -> Bool 1089moreRelevant = (<=) 1090 1091-- | Equality ignoring origin. 1092sameRelevance :: Relevance -> Relevance -> Bool 1093sameRelevance = (==) 1094 1095-- | More relevant is smaller. 1096instance Ord Relevance where 1097 compare = curry $ \case 1098 (r, r') | r == r' -> EQ 1099 -- top 1100 (_, Irrelevant) -> LT 1101 (Irrelevant, _) -> GT 1102 -- bottom 1103 (Relevant, _) -> LT 1104 (_, Relevant) -> GT 1105 -- redundant case 1106 (NonStrict,NonStrict) -> EQ 1107 1108-- | More relevant is smaller. 1109instance PartialOrd Relevance where 1110 comparable = comparableOrd 1111 1112-- | @usableRelevance rel == False@ iff we cannot use a variable of @rel@. 1113usableRelevance :: LensRelevance a => a -> Bool 1114usableRelevance = isRelevant 1115 1116-- | 'Relevance' composition. 1117-- 'Irrelevant' is dominant, 'Relevant' is neutral. 1118-- Composition coincides with 'max'. 1119composeRelevance :: Relevance -> Relevance -> Relevance 1120composeRelevance r r' = 1121 case (r, r') of 1122 (Irrelevant, _) -> Irrelevant 1123 (_, Irrelevant) -> Irrelevant 1124 (NonStrict, _) -> NonStrict 1125 (_, NonStrict) -> NonStrict 1126 (Relevant, Relevant) -> Relevant 1127 1128-- | Compose with relevance flag from the left. 1129-- This function is e.g. used to update the relevance information 1130-- on pattern variables @a@ after a match against something @rel@. 1131applyRelevance :: LensRelevance a => Relevance -> a -> a 1132applyRelevance rel = mapRelevance (rel `composeRelevance`) 1133 1134-- | @inverseComposeRelevance r x@ returns the most irrelevant @y@ 1135-- such that forall @x@, @y@ we have 1136-- @x \`moreRelevant\` (r \`composeRelevance\` y)@ 1137-- iff 1138-- @(r \`inverseComposeRelevance\` x) \`moreRelevant\` y@ (Galois connection). 1139inverseComposeRelevance :: Relevance -> Relevance -> Relevance 1140inverseComposeRelevance r x = 1141 case (r, x) of 1142 (Relevant , x) -> x -- going to relevant arg.: nothing changes 1143 -- because Relevant is comp.-neutral 1144 (Irrelevant, x) -> Relevant -- going irrelevant: every thing usable 1145 (NonStrict , Irrelevant) -> Irrelevant -- otherwise: irrelevant things remain unusable 1146 (NonStrict , _) -> Relevant -- but @NonStrict@s become usable 1147 1148-- | Left division by a 'Relevance'. 1149-- Used e.g. to modify context when going into a @rel@ argument. 1150inverseApplyRelevance :: LensRelevance a => Relevance -> a -> a 1151inverseApplyRelevance rel = mapRelevance (rel `inverseComposeRelevance`) 1152 1153-- | 'Relevance' forms a semigroup under composition. 1154instance Semigroup (UnderComposition Relevance) where 1155 (<>) = liftA2 composeRelevance 1156 1157-- | 'Relevant' is the unit under composition. 1158instance Monoid (UnderComposition Relevance) where 1159 mempty = pure unitRelevance 1160 mappend = (<>) 1161 1162instance POSemigroup (UnderComposition Relevance) where 1163instance POMonoid (UnderComposition Relevance) where 1164 1165instance LeftClosedPOMonoid (UnderComposition Relevance) where 1166 inverseCompose = liftA2 inverseComposeRelevance 1167 1168instance Semigroup (UnderAddition Relevance) where 1169 (<>) = liftA2 addRelevance 1170 1171instance Monoid (UnderAddition Relevance) where 1172 mempty = pure zeroRelevance 1173 mappend = (<>) 1174 1175instance POSemigroup (UnderAddition Relevance) where 1176instance POMonoid (UnderAddition Relevance) where 1177 1178-- | Combine inferred 'Relevance'. 1179-- The unit is 'Irrelevant'. 1180addRelevance :: Relevance -> Relevance -> Relevance 1181addRelevance = min 1182 1183-- | 'Relevance' forms a monoid under addition, and even a semiring. 1184zeroRelevance :: Relevance 1185zeroRelevance = Irrelevant 1186 1187-- | Identity element under composition 1188unitRelevance :: Relevance 1189unitRelevance = Relevant 1190 1191-- | Absorptive element under addition. 1192topRelevance :: Relevance 1193topRelevance = Relevant 1194 1195-- | Default Relevance is the identity element under composition 1196defaultRelevance :: Relevance 1197defaultRelevance = unitRelevance 1198 1199-- | Irrelevant function arguments may appear non-strictly in the codomain type. 1200irrToNonStrict :: Relevance -> Relevance 1201irrToNonStrict Irrelevant = NonStrict 1202irrToNonStrict rel = rel 1203 1204-- | Applied when working on types (unless --experimental-irrelevance). 1205nonStrictToRel :: Relevance -> Relevance 1206nonStrictToRel NonStrict = Relevant 1207nonStrictToRel rel = rel 1208 1209nonStrictToIrr :: Relevance -> Relevance 1210nonStrictToIrr NonStrict = Irrelevant 1211nonStrictToIrr rel = rel 1212 1213 1214--------------------------------------------------------------------------- 1215-- * Annotations 1216--------------------------------------------------------------------------- 1217 1218-- | We have a tuple of annotations, which might not be fully orthogonal. 1219data Annotation = Annotation 1220 { annLock :: Lock 1221 -- ^ Fitch-style dependent right adjoints. 1222 -- See Modal Dependent Type Theory and Dependent Right Adjoints, arXiv:1804.05236. 1223 } deriving (Data, Eq, Ord, Show, Generic) 1224 1225instance HasRange Annotation where 1226 getRange _ = noRange 1227 1228instance KillRange Annotation where 1229 killRange = id 1230 1231defaultAnnotation :: Annotation 1232defaultAnnotation = Annotation defaultLock 1233 1234instance NFData Annotation where 1235 rnf (Annotation l) = rnf l 1236 1237class LensAnnotation a where 1238 1239 getAnnotation :: a -> Annotation 1240 1241 setAnnotation :: Annotation -> a -> a 1242 1243 mapAnnotation :: (Annotation -> Annotation) -> a -> a 1244 mapAnnotation f a = setAnnotation (f $ getAnnotation a) a 1245 1246 default getAnnotation :: LensArgInfo a => a -> Annotation 1247 getAnnotation = argInfoAnnotation . getArgInfo 1248 1249 default setAnnotation :: LensArgInfo a => Annotation -> a -> a 1250 setAnnotation a = mapArgInfo $ \ ai -> ai { argInfoAnnotation = a } 1251 1252instance LensAnnotation Annotation where 1253 getAnnotation = id 1254 setAnnotation = const 1255 mapAnnotation = id 1256 1257instance LensAnnotation (Arg t) where 1258 getAnnotation = getAnnotation . getArgInfo 1259 setAnnotation = mapArgInfo . setAnnotation 1260 1261 1262--------------------------------------------------------------------------- 1263-- * Locks 1264--------------------------------------------------------------------------- 1265 1266data Lock = IsNotLock 1267 | IsLock -- ^ In the future there might be different kinds of them. 1268 -- For now we assume lock weakening. 1269 deriving (Data, Show, Generic, Eq, Enum, Bounded, Ord) 1270 1271defaultLock :: Lock 1272defaultLock = IsNotLock 1273 1274instance NFData Lock where 1275 rnf IsNotLock = () 1276 rnf IsLock = () 1277 1278class LensLock a where 1279 1280 getLock :: a -> Lock 1281 1282 setLock :: Lock -> a -> a 1283 setLock = mapLock . const 1284 1285 mapLock :: (Lock -> Lock) -> a -> a 1286 mapLock f a = setLock (f $ getLock a) a 1287 1288instance LensLock Lock where 1289 getLock = id 1290 setLock = const 1291 mapLock = id 1292 1293instance LensLock ArgInfo where 1294 getLock = annLock . argInfoAnnotation 1295 setLock l info = info { argInfoAnnotation = Annotation l } 1296 1297instance LensLock (Arg t) where 1298 getLock = getLock . getArgInfo 1299 setLock = mapArgInfo . setLock 1300 1301--------------------------------------------------------------------------- 1302-- * Cohesion 1303--------------------------------------------------------------------------- 1304 1305-- | Cohesion modalities 1306-- see "Brouwer's fixed-point theorem in real-cohesive homotopy type theory" (arXiv:1509.07584) 1307-- types are now given an additional topological layer which the modalities interact with. 1308data Cohesion 1309 = Flat -- ^ same points, discrete topology, idempotent comonad, box-like. 1310 | Continuous -- ^ identity modality. 1311 -- | Sharp -- ^ same points, codiscrete topology, idempotent monad, diamond-like. 1312 | Squash -- ^ single point space, artificially added for Flat left-composition. 1313 deriving (Data, Show, Eq, Enum, Bounded, Generic) 1314 1315allCohesions :: [Cohesion] 1316allCohesions = [minBound..maxBound] 1317 1318instance HasRange Cohesion where 1319 getRange _ = noRange 1320 1321instance SetRange Cohesion where 1322 setRange _ = id 1323 1324instance KillRange Cohesion where 1325 killRange rel = rel -- no range to kill 1326 1327instance NFData Cohesion where 1328 rnf Flat = () 1329 rnf Continuous = () 1330 rnf Squash = () 1331 1332-- | A lens to access the 'Cohesion' attribute in data structures. 1333-- Minimal implementation: @getCohesion@ and @mapCohesion@ or @LensModality@. 1334class LensCohesion a where 1335 1336 getCohesion :: a -> Cohesion 1337 1338 setCohesion :: Cohesion -> a -> a 1339 setCohesion h = mapCohesion (const h) 1340 1341 mapCohesion :: (Cohesion -> Cohesion) -> a -> a 1342 1343 default getCohesion :: LensModality a => a -> Cohesion 1344 getCohesion = modCohesion . getModality 1345 1346 default mapCohesion :: LensModality a => (Cohesion -> Cohesion) -> a -> a 1347 mapCohesion f = mapModality $ \ ai -> ai { modCohesion = f $ modCohesion ai } 1348 1349instance LensCohesion Cohesion where 1350 getCohesion = id 1351 setCohesion = const 1352 mapCohesion = id 1353 1354-- | Information ordering. 1355-- @Flat \`moreCohesion\` 1356-- Continuous \`moreCohesion\` 1357-- Sharp \`moreCohesion\` 1358-- Squash@ 1359moreCohesion :: Cohesion -> Cohesion -> Bool 1360moreCohesion = (<=) 1361 1362-- | Equality ignoring origin. 1363sameCohesion :: Cohesion -> Cohesion -> Bool 1364sameCohesion = (==) 1365 1366-- | Order is given by implication: flatter is smaller. 1367instance Ord Cohesion where 1368 compare = curry $ \case 1369 (r, r') | r == r' -> EQ 1370 -- top 1371 (_, Squash) -> LT 1372 (Squash, _) -> GT 1373 -- bottom 1374 (Flat, _) -> LT 1375 (_, Flat) -> GT 1376 -- redundant case 1377 (Continuous,Continuous) -> EQ 1378 1379-- | Flatter is smaller. 1380instance PartialOrd Cohesion where 1381 comparable = comparableOrd 1382 1383-- | @usableCohesion rel == False@ iff we cannot use a variable of @rel@. 1384usableCohesion :: LensCohesion a => a -> Bool 1385usableCohesion a = getCohesion a `moreCohesion` Continuous 1386 1387-- | 'Cohesion' composition. 1388-- 'Squash' is dominant, 'Continuous' is neutral. 1389composeCohesion :: Cohesion -> Cohesion -> Cohesion 1390composeCohesion r r' = 1391 case (r, r') of 1392 (Squash, _) -> Squash 1393 (_, Squash) -> Squash 1394 (Flat, _) -> Flat 1395 (_, Flat) -> Flat 1396 (Continuous, Continuous) -> Continuous 1397 1398-- | Compose with cohesion flag from the left. 1399-- This function is e.g. used to update the cohesion information 1400-- on pattern variables @a@ after a match against something of cohesion @rel@. 1401applyCohesion :: LensCohesion a => Cohesion -> a -> a 1402applyCohesion rel = mapCohesion (rel `composeCohesion`) 1403 1404-- | @inverseComposeCohesion r x@ returns the least @y@ 1405-- such that forall @x@, @y@ we have 1406-- @x \`moreCohesion\` (r \`composeCohesion\` y)@ 1407-- iff 1408-- @(r \`inverseComposeCohesion\` x) \`moreCohesion\` y@ (Galois connection). 1409-- The above law fails for @r = Squash@. 1410inverseComposeCohesion :: Cohesion -> Cohesion -> Cohesion 1411inverseComposeCohesion r x = 1412 case (r, x) of 1413 (Continuous , x) -> x -- going to continous arg.: nothing changes 1414 -- because Continuous is comp.-neutral 1415 (Squash, x) -> Squash -- artificial case, should not be needed. 1416 (Flat , Flat) -> Flat -- otherwise: Flat things remain Flat 1417 (Flat , _) -> Squash -- but everything else becomes unusable. 1418 1419-- | Left division by a 'Cohesion'. 1420-- Used e.g. to modify context when going into a @rel@ argument. 1421inverseApplyCohesion :: LensCohesion a => Cohesion -> a -> a 1422inverseApplyCohesion rel = mapCohesion (rel `inverseComposeCohesion`) 1423 1424-- | 'Cohesion' forms a semigroup under composition. 1425instance Semigroup (UnderComposition Cohesion) where 1426 (<>) = liftA2 composeCohesion 1427 1428-- | 'Continous' is the multiplicative unit. 1429instance Monoid (UnderComposition Cohesion) where 1430 mempty = pure unitCohesion 1431 mappend = (<>) 1432 1433instance POSemigroup (UnderComposition Cohesion) where 1434instance POMonoid (UnderComposition Cohesion) where 1435 1436instance LeftClosedPOMonoid (UnderComposition Cohesion) where 1437 inverseCompose = liftA2 inverseComposeCohesion 1438 1439-- | 'Cohesion' forms a semigroup under addition. 1440instance Semigroup (UnderAddition Cohesion) where 1441 (<>) = liftA2 addCohesion 1442 1443-- | 'Squash' is the additive unit. 1444instance Monoid (UnderAddition Cohesion) where 1445 mempty = pure zeroCohesion 1446 mappend = (<>) 1447 1448instance POSemigroup (UnderAddition Cohesion) where 1449instance POMonoid (UnderAddition Cohesion) where 1450 1451-- | Combine inferred 'Cohesion'. 1452-- The unit is 'Squash'. 1453addCohesion :: Cohesion -> Cohesion -> Cohesion 1454addCohesion = min 1455 1456-- | 'Cohesion' forms a monoid under addition, and even a semiring. 1457zeroCohesion :: Cohesion 1458zeroCohesion = Squash 1459 1460-- | Identity under composition 1461unitCohesion :: Cohesion 1462unitCohesion = Continuous 1463 1464-- | Absorptive element under addition. 1465topCohesion :: Cohesion 1466topCohesion = Flat 1467 1468-- | Default Cohesion is the identity element under composition 1469defaultCohesion :: Cohesion 1470defaultCohesion = unitCohesion 1471 1472--------------------------------------------------------------------------- 1473-- * Origin of arguments (user-written, inserted or reflected) 1474--------------------------------------------------------------------------- 1475 1476-- | Origin of arguments. 1477data Origin 1478 = UserWritten -- ^ From the source file / user input. (Preserve!) 1479 | Inserted -- ^ E.g. inserted hidden arguments. 1480 | Reflected -- ^ Produced by the reflection machinery. 1481 | CaseSplit -- ^ Produced by an interactive case split. 1482 | Substitution -- ^ Named application produced to represent a substitution. E.g. "?0 (x = n)" instead of "?0 n" 1483 deriving (Data, Show, Eq, Ord) 1484 1485instance HasRange Origin where 1486 getRange _ = noRange 1487 1488instance KillRange Origin where 1489 killRange = id 1490 1491instance NFData Origin where 1492 rnf UserWritten = () 1493 rnf Inserted = () 1494 rnf Reflected = () 1495 rnf CaseSplit = () 1496 rnf Substitution = () 1497 1498-- | Decorating something with 'Origin' information. 1499data WithOrigin a = WithOrigin 1500 { woOrigin :: !Origin 1501 , woThing :: a 1502 } 1503 deriving (Data, Eq, Ord, Show, Functor, Foldable, Traversable) 1504 1505instance Decoration WithOrigin where 1506 traverseF f (WithOrigin h a) = WithOrigin h <$> f a 1507 1508instance Pretty a => Pretty (WithOrigin a) where 1509 prettyPrec p = prettyPrec p . woThing 1510 1511instance HasRange a => HasRange (WithOrigin a) where 1512 getRange = getRange . dget 1513 1514instance SetRange a => SetRange (WithOrigin a) where 1515 setRange = fmap . setRange 1516 1517instance KillRange a => KillRange (WithOrigin a) where 1518 killRange = fmap killRange 1519 1520instance NFData a => NFData (WithOrigin a) where 1521 rnf (WithOrigin _ a) = rnf a 1522 1523-- | A lens to access the 'Origin' attribute in data structures. 1524-- Minimal implementation: @getOrigin@ and @mapOrigin@ or @LensArgInfo@. 1525 1526class LensOrigin a where 1527 1528 getOrigin :: a -> Origin 1529 1530 setOrigin :: Origin -> a -> a 1531 setOrigin o = mapOrigin (const o) 1532 1533 mapOrigin :: (Origin -> Origin) -> a -> a 1534 1535 default getOrigin :: LensArgInfo a => a -> Origin 1536 getOrigin = argInfoOrigin . getArgInfo 1537 1538 default mapOrigin :: LensArgInfo a => (Origin -> Origin) -> a -> a 1539 mapOrigin f = mapArgInfo $ \ ai -> ai { argInfoOrigin = f $ argInfoOrigin ai } 1540 1541instance LensOrigin Origin where 1542 getOrigin = id 1543 setOrigin = const 1544 mapOrigin = id 1545 1546instance LensOrigin (WithOrigin a) where 1547 getOrigin (WithOrigin h _) = h 1548 setOrigin h (WithOrigin _ a) = WithOrigin h a 1549 mapOrigin f (WithOrigin h a) = WithOrigin (f h) a 1550 1551----------------------------------------------------------------------------- 1552-- * Free variable annotations 1553----------------------------------------------------------------------------- 1554 1555data FreeVariables = UnknownFVs | KnownFVs IntSet 1556 deriving (Data, Eq, Ord, Show) 1557 1558instance Semigroup FreeVariables where 1559 UnknownFVs <> _ = UnknownFVs 1560 _ <> UnknownFVs = UnknownFVs 1561 KnownFVs vs1 <> KnownFVs vs2 = KnownFVs (IntSet.union vs1 vs2) 1562 1563instance Monoid FreeVariables where 1564 mempty = KnownFVs IntSet.empty 1565 mappend = (<>) 1566 1567instance KillRange FreeVariables where 1568 killRange = id 1569 1570instance NFData FreeVariables where 1571 rnf UnknownFVs = () 1572 rnf (KnownFVs fv) = rnf fv 1573 1574unknownFreeVariables :: FreeVariables 1575unknownFreeVariables = UnknownFVs 1576 1577noFreeVariables :: FreeVariables 1578noFreeVariables = mempty 1579 1580oneFreeVariable :: Int -> FreeVariables 1581oneFreeVariable = KnownFVs . IntSet.singleton 1582 1583freeVariablesFromList :: [Int] -> FreeVariables 1584freeVariablesFromList = mconcat . map oneFreeVariable 1585 1586-- | A lens to access the 'FreeVariables' attribute in data structures. 1587-- Minimal implementation: @getFreeVariables@ and @mapFreeVariables@ or @LensArgInfo@. 1588class LensFreeVariables a where 1589 1590 getFreeVariables :: a -> FreeVariables 1591 1592 setFreeVariables :: FreeVariables -> a -> a 1593 setFreeVariables o = mapFreeVariables (const o) 1594 1595 mapFreeVariables :: (FreeVariables -> FreeVariables) -> a -> a 1596 1597 default getFreeVariables :: LensArgInfo a => a -> FreeVariables 1598 getFreeVariables = argInfoFreeVariables . getArgInfo 1599 1600 default mapFreeVariables :: LensArgInfo a => (FreeVariables -> FreeVariables) -> a -> a 1601 mapFreeVariables f = mapArgInfo $ \ ai -> ai { argInfoFreeVariables = f $ argInfoFreeVariables ai } 1602 1603instance LensFreeVariables FreeVariables where 1604 getFreeVariables = id 1605 setFreeVariables = const 1606 mapFreeVariables = id 1607 1608hasNoFreeVariables :: LensFreeVariables a => a -> Bool 1609hasNoFreeVariables x = 1610 case getFreeVariables x of 1611 UnknownFVs -> False 1612 KnownFVs fv -> IntSet.null fv 1613 1614--------------------------------------------------------------------------- 1615-- * Argument decoration 1616--------------------------------------------------------------------------- 1617 1618-- | A function argument can be hidden and/or irrelevant. 1619 1620data ArgInfo = ArgInfo 1621 { argInfoHiding :: Hiding 1622 , argInfoModality :: Modality 1623 , argInfoOrigin :: Origin 1624 , argInfoFreeVariables :: FreeVariables 1625 , argInfoAnnotation :: Annotation 1626 -- ^ Sometimes we want a different kind of binder/pi-type, without it 1627 -- supporting any of the @Modality@ interface. 1628 } deriving (Data, Eq, Ord, Show) 1629 1630instance HasRange ArgInfo where 1631 getRange (ArgInfo h m o _fv a) = getRange (h, m, o, a) 1632 1633instance KillRange ArgInfo where 1634 killRange (ArgInfo h m o fv a) = killRange5 ArgInfo h m o fv a 1635 1636class LensArgInfo a where 1637 getArgInfo :: a -> ArgInfo 1638 setArgInfo :: ArgInfo -> a -> a 1639 setArgInfo ai = mapArgInfo (const ai) 1640 mapArgInfo :: (ArgInfo -> ArgInfo) -> a -> a 1641 mapArgInfo f a = setArgInfo (f $ getArgInfo a) a 1642 1643instance LensArgInfo ArgInfo where 1644 getArgInfo = id 1645 setArgInfo = const 1646 mapArgInfo = id 1647 1648instance NFData ArgInfo where 1649 rnf (ArgInfo a b c d e) = rnf a `seq` rnf b `seq` rnf c `seq` rnf d `seq` rnf e 1650 1651instance LensHiding ArgInfo where 1652 getHiding = argInfoHiding 1653 setHiding h ai = ai { argInfoHiding = h } 1654 mapHiding f ai = ai { argInfoHiding = f (argInfoHiding ai) } 1655 1656instance LensModality ArgInfo where 1657 getModality = argInfoModality 1658 setModality m ai = ai { argInfoModality = m } 1659 mapModality f ai = ai { argInfoModality = f (argInfoModality ai) } 1660 1661instance LensOrigin ArgInfo where 1662 getOrigin = argInfoOrigin 1663 setOrigin o ai = ai { argInfoOrigin = o } 1664 mapOrigin f ai = ai { argInfoOrigin = f (argInfoOrigin ai) } 1665 1666instance LensFreeVariables ArgInfo where 1667 getFreeVariables = argInfoFreeVariables 1668 setFreeVariables o ai = ai { argInfoFreeVariables = o } 1669 mapFreeVariables f ai = ai { argInfoFreeVariables = f (argInfoFreeVariables ai) } 1670 1671instance LensAnnotation ArgInfo where 1672 getAnnotation = argInfoAnnotation 1673 setAnnotation m ai = ai { argInfoAnnotation = m } 1674 mapAnnotation f ai = ai { argInfoAnnotation = f (argInfoAnnotation ai) } 1675 1676-- inherited instances 1677 1678instance LensRelevance ArgInfo where 1679 getRelevance = getRelevanceMod 1680 setRelevance = setRelevanceMod 1681 mapRelevance = mapRelevanceMod 1682 1683instance LensQuantity ArgInfo where 1684 getQuantity = getQuantityMod 1685 setQuantity = setQuantityMod 1686 mapQuantity = mapQuantityMod 1687 1688instance LensCohesion ArgInfo where 1689 getCohesion = getCohesionMod 1690 setCohesion = setCohesionMod 1691 mapCohesion = mapCohesionMod 1692 1693defaultArgInfo :: ArgInfo 1694defaultArgInfo = ArgInfo 1695 { argInfoHiding = NotHidden 1696 , argInfoModality = defaultModality 1697 , argInfoOrigin = UserWritten 1698 , argInfoFreeVariables = UnknownFVs 1699 , argInfoAnnotation = defaultAnnotation 1700 } 1701 1702-- Accessing through ArgInfo 1703 1704-- default accessors for Hiding 1705 1706getHidingArgInfo :: LensArgInfo a => LensGet Hiding a 1707getHidingArgInfo = getHiding . getArgInfo 1708 1709setHidingArgInfo :: LensArgInfo a => LensSet Hiding a 1710setHidingArgInfo = mapArgInfo . setHiding 1711 1712mapHidingArgInfo :: LensArgInfo a => LensMap Hiding a 1713mapHidingArgInfo = mapArgInfo . mapHiding 1714 1715-- default accessors for Modality 1716 1717getModalityArgInfo :: LensArgInfo a => LensGet Modality a 1718getModalityArgInfo = getModality . getArgInfo 1719 1720setModalityArgInfo :: LensArgInfo a => LensSet Modality a 1721setModalityArgInfo = mapArgInfo . setModality 1722 1723mapModalityArgInfo :: LensArgInfo a => LensMap Modality a 1724mapModalityArgInfo = mapArgInfo . mapModality 1725 1726-- default accessors for Origin 1727 1728getOriginArgInfo :: LensArgInfo a => LensGet Origin a 1729getOriginArgInfo = getOrigin . getArgInfo 1730 1731setOriginArgInfo :: LensArgInfo a => LensSet Origin a 1732setOriginArgInfo = mapArgInfo . setOrigin 1733 1734mapOriginArgInfo :: LensArgInfo a => LensMap Origin a 1735mapOriginArgInfo = mapArgInfo . mapOrigin 1736 1737-- default accessors for FreeVariables 1738 1739getFreeVariablesArgInfo :: LensArgInfo a => LensGet FreeVariables a 1740getFreeVariablesArgInfo = getFreeVariables . getArgInfo 1741 1742setFreeVariablesArgInfo :: LensArgInfo a => LensSet FreeVariables a 1743setFreeVariablesArgInfo = mapArgInfo . setFreeVariables 1744 1745mapFreeVariablesArgInfo :: LensArgInfo a => LensMap FreeVariables a 1746mapFreeVariablesArgInfo = mapArgInfo . mapFreeVariables 1747 1748-- inserted hidden arguments 1749 1750isInsertedHidden :: (LensHiding a, LensOrigin a) => a -> Bool 1751isInsertedHidden a = getHiding a == Hidden && getOrigin a == Inserted 1752 1753--------------------------------------------------------------------------- 1754-- * Arguments 1755--------------------------------------------------------------------------- 1756 1757data Arg e = Arg 1758 { argInfo :: ArgInfo 1759 , unArg :: e 1760 } deriving (Data, Eq, Ord, Show, Functor, Foldable, Traversable) 1761 1762instance Decoration Arg where 1763 traverseF f (Arg ai a) = Arg ai <$> f a 1764 1765instance HasRange a => HasRange (Arg a) where 1766 getRange = getRange . unArg 1767 1768instance SetRange a => SetRange (Arg a) where 1769 setRange r = fmap $ setRange r 1770 1771instance KillRange a => KillRange (Arg a) where 1772 killRange (Arg info a) = killRange2 Arg info a 1773 1774-- Andreas, 2019-07-05, issue #3889 1775-- A dedicated equality for with-abstraction now exists, 1776-- thus, we can use intensional equality for Arg. 1777-- 1778-- -- | Ignores 'Quantity', 'Relevance', 'Origin', and 'FreeVariables'. 1779-- -- Ignores content of argument if 'Irrelevant'. 1780-- -- 1781-- instance Eq a => Eq (Arg a) where 1782-- Arg (ArgInfo h1 m1 _ _) x1 == Arg (ArgInfo h2 m2 _ _) x2 = 1783-- h1 == h2 && (isIrrelevant m1 || isIrrelevant m2 || x1 == x2) 1784-- -- Andreas, 2017-10-04, issue #2775, ignore irrelevant arguments during with-abstraction. 1785-- -- This is a hack, we should not use '(==)' in with-abstraction 1786-- -- and more generally not use it on Syntax. 1787-- -- Andrea: except for caching. 1788 1789-- instance Show a => Show (Arg a) where 1790-- show (Arg (ArgInfo h (Modality r q) o fv) a) = showFVs fv $ showQ q $ showR r $ showO o $ showH h $ show a 1791-- where 1792-- showH Hidden s = "{" ++ s ++ "}" 1793-- showH NotHidden s = "(" ++ s ++ ")" 1794-- showH (Instance o) s = showOv o ++ "{{" ++ s ++ "}}" 1795-- where showOv YesOverlap = "overlap " 1796-- showOv NoOverlap = "" 1797-- showR r s = case r of 1798-- Irrelevant -> "." ++ s 1799-- NonStrict -> "?" ++ s 1800-- Relevant -> "r" ++ s -- Andreas: I want to see it explicitly 1801-- showQ q s = case q of 1802-- Quantity0 -> "0" ++ s 1803-- Quantity1 -> "1" ++ s 1804-- Quantityω -> "ω" ++ s 1805-- showO o s = case o of 1806-- UserWritten -> "u" ++ s 1807-- Inserted -> "i" ++ s 1808-- Reflected -> "g" ++ s -- generated by reflection 1809-- CaseSplit -> "c" ++ s -- generated by case split 1810-- Substitution -> "s" ++ s 1811-- showFVs UnknownFVs s = s 1812-- showFVs (KnownFVs fv) s = "fv" ++ show (IntSet.toList fv) ++ s 1813 1814-- -- defined in Concrete.Pretty 1815-- instance Pretty a => Pretty (Arg a) where 1816-- pretty (Arg (ArgInfo h (Modality r q) o fv) a) = prettyFVs fv $ prettyQ q $ prettyR r $ prettyO o $ prettyH h $ pretty a 1817-- where 1818-- prettyH Hidden s = "{" <> s <> "}" 1819-- prettyH NotHidden s = "(" <> s <> ")" 1820-- prettyH (Instance o) s = prettyOv o <> "{{" <> s <> "}}" 1821-- where prettyOv YesOverlap = "overlap " 1822-- prettyOv NoOverlap = "" 1823-- prettyR r s = case r of 1824-- Irrelevant -> "." <> s 1825-- NonStrict -> "?" <> s 1826-- Relevant -> "r" <> s -- Andreas: I want to see it explicitly 1827-- prettyQ q s = case q of 1828-- Quantity0 -> "0" <> s 1829-- Quantity1 -> "1" <> s 1830-- Quantityω -> "ω" <> s 1831-- prettyO o s = case o of 1832-- UserWritten -> "u" <> s 1833-- Inserted -> "i" <> s 1834-- Reflected -> "g" <> s -- generated by reflection 1835-- CaseSplit -> "c" <> s -- generated by case split 1836-- Substitution -> "s" <> s 1837-- prettyFVs UnknownFVs s = s 1838-- prettyFVs (KnownFVs fv) s = "fv" <> pretty (IntSet.toList fv) <> s 1839 1840instance NFData e => NFData (Arg e) where 1841 rnf (Arg a b) = rnf a `seq` rnf b 1842 1843instance LensArgInfo (Arg a) where 1844 getArgInfo = argInfo 1845 setArgInfo ai arg = arg { argInfo = ai } 1846 mapArgInfo f arg = arg { argInfo = f $ argInfo arg } 1847 1848-- The other lenses are defined through LensArgInfo 1849 1850instance LensHiding (Arg e) where 1851 getHiding = getHidingArgInfo 1852 setHiding = setHidingArgInfo 1853 mapHiding = mapHidingArgInfo 1854 1855instance LensModality (Arg e) where 1856 getModality = getModalityArgInfo 1857 setModality = setModalityArgInfo 1858 mapModality = mapModalityArgInfo 1859 1860instance LensOrigin (Arg e) where 1861 getOrigin = getOriginArgInfo 1862 setOrigin = setOriginArgInfo 1863 mapOrigin = mapOriginArgInfo 1864 1865instance LensFreeVariables (Arg e) where 1866 getFreeVariables = getFreeVariablesArgInfo 1867 setFreeVariables = setFreeVariablesArgInfo 1868 mapFreeVariables = mapFreeVariablesArgInfo 1869 1870-- Since we have LensModality, we get relevance and quantity by default 1871 1872instance LensRelevance (Arg e) where 1873 getRelevance = getRelevanceMod 1874 setRelevance = setRelevanceMod 1875 mapRelevance = mapRelevanceMod 1876 1877instance LensQuantity (Arg e) where 1878 getQuantity = getQuantityMod 1879 setQuantity = setQuantityMod 1880 mapQuantity = mapQuantityMod 1881 1882instance LensCohesion (Arg e) where 1883 getCohesion = getCohesionMod 1884 setCohesion = setCohesionMod 1885 mapCohesion = mapCohesionMod 1886 1887defaultArg :: a -> Arg a 1888defaultArg = Arg defaultArgInfo 1889 1890-- | @xs \`withArgsFrom\` args@ translates @xs@ into a list of 'Arg's, 1891-- using the elements in @args@ to fill in the non-'unArg' fields. 1892-- 1893-- Precondition: The two lists should have equal length. 1894 1895withArgsFrom :: [a] -> [Arg b] -> [Arg a] 1896xs `withArgsFrom` args = 1897 zipWith (\x arg -> fmap (const x) arg) xs args 1898 1899withNamedArgsFrom :: [a] -> [NamedArg b] -> [NamedArg a] 1900xs `withNamedArgsFrom` args = 1901 zipWith (\x -> fmap (x <$)) xs args 1902 1903--------------------------------------------------------------------------- 1904-- * Names 1905--------------------------------------------------------------------------- 1906 1907class Eq a => Underscore a where 1908 underscore :: a 1909 isUnderscore :: a -> Bool 1910 isUnderscore = (== underscore) 1911 1912instance Underscore String where 1913 underscore = "_" 1914 1915instance Underscore ByteString where 1916 underscore = ByteString.pack underscore 1917 1918instance Underscore Doc where 1919 underscore = text underscore 1920 1921--------------------------------------------------------------------------- 1922-- * Named arguments 1923--------------------------------------------------------------------------- 1924 1925-- | Something potentially carrying a name. 1926data Named name a = 1927 Named { nameOf :: Maybe name 1928 , namedThing :: a 1929 } 1930 deriving (Eq, Ord, Show, Data, Functor, Foldable, Traversable) 1931 1932-- | Standard naming. 1933type Named_ = Named NamedName 1934 1935-- | Standard argument names. 1936type NamedName = WithOrigin (Ranged ArgName) 1937 1938-- | Equality of argument names of things modulo 'Range' and 'Origin'. 1939sameName :: NamedName -> NamedName -> Bool 1940sameName = (==) `on` (rangedThing . woThing) 1941 1942unnamed :: a -> Named name a 1943unnamed = Named Nothing 1944 1945isUnnamed :: Named name a -> Maybe a 1946isUnnamed = \case 1947 Named Nothing a -> Just a 1948 Named Just{} a -> Nothing 1949 1950named :: name -> a -> Named name a 1951named = Named . Just 1952 1953userNamed :: Ranged ArgName -> a -> Named_ a 1954userNamed = Named . Just . WithOrigin UserWritten 1955 1956-- | Accessor/editor for the 'nameOf' component. 1957class LensNamed a where 1958 -- | The type of the name 1959 type NameOf a 1960 lensNamed :: Lens' (Maybe (NameOf a)) a 1961 1962 -- Lenses lift through decorations: 1963 default lensNamed :: (Decoration f, LensNamed b, NameOf b ~ NameOf a, f b ~ a) => Lens' (Maybe (NameOf a)) a 1964 lensNamed = traverseF . lensNamed 1965 1966instance LensNamed a => LensNamed (Arg a) where 1967 type NameOf (Arg a) = NameOf a 1968 1969instance LensNamed (Maybe a) where 1970 type NameOf (Maybe a) = a 1971 lensNamed = id 1972 1973instance LensNamed (Named name a) where 1974 type NameOf (Named name a) = name 1975 1976 lensNamed f (Named mn a) = f mn <&> \ mn' -> Named mn' a 1977 1978getNameOf :: LensNamed a => a -> Maybe (NameOf a) 1979getNameOf a = a ^. lensNamed 1980 1981setNameOf :: LensNamed a => Maybe (NameOf a) -> a -> a 1982setNameOf = set lensNamed 1983 1984mapNameOf :: LensNamed a => (Maybe (NameOf a) -> Maybe (NameOf a)) -> a -> a 1985mapNameOf = over lensNamed 1986bareNameOf :: (LensNamed a, NameOf a ~ NamedName) => a -> Maybe ArgName 1987bareNameOf a = rangedThing . woThing <$> getNameOf a 1988 1989bareNameWithDefault :: (LensNamed a, NameOf a ~ NamedName) => ArgName -> a -> ArgName 1990bareNameWithDefault x a = maybe x (rangedThing . woThing) $ getNameOf a 1991 1992-- | Equality of argument names of things modulo 'Range' and 'Origin'. 1993namedSame :: (LensNamed a, LensNamed b, NameOf a ~ NamedName, NameOf b ~ NamedName) => a -> b -> Bool 1994namedSame a b = case (getNameOf a, getNameOf b) of 1995 (Nothing, Nothing) -> True 1996 (Just x , Just y ) -> sameName x y 1997 _ -> False 1998 1999-- | Does an argument @arg@ fit the shape @dom@ of the next expected argument? 2000-- 2001-- The hiding has to match, and if the argument has a name, it should match 2002-- the name of the domain. 2003-- 2004-- 'Nothing' should be '__IMPOSSIBLE__', so use as 2005-- @@ 2006-- fromMaybe __IMPOSSIBLE__ $ fittingNamedArg arg dom 2007-- @@ 2008-- 2009fittingNamedArg 2010 :: ( LensNamed arg, NameOf arg ~ NamedName, LensHiding arg 2011 , LensNamed dom, NameOf dom ~ NamedName, LensHiding dom ) 2012 => arg -> dom -> Maybe Bool 2013fittingNamedArg arg dom 2014 | not $ sameHiding arg dom = no 2015 | visible arg = yes 2016 | otherwise = 2017 caseMaybe (bareNameOf arg) yes $ \ x -> 2018 caseMaybe (bareNameOf dom) impossible $ \ y -> 2019 return $ x == y 2020 where 2021 yes = return True 2022 no = return False 2023 impossible = Nothing 2024 2025-- Standard instances for 'Named': 2026 2027instance Decoration (Named name) where 2028 traverseF f (Named n a) = Named n <$> f a 2029 2030instance HasRange a => HasRange (Named name a) where 2031 getRange = getRange . namedThing 2032 2033instance SetRange a => SetRange (Named name a) where 2034 setRange r = fmap $ setRange r 2035 2036instance (KillRange name, KillRange a) => KillRange (Named name a) where 2037 killRange (Named n a) = Named (killRange n) (killRange a) 2038 2039-- instance Show a => Show (Named_ a) where 2040-- show (Named Nothing a) = show a 2041-- show (Named (Just n) a) = rawNameToString (rangedThing n) ++ " = " ++ show a 2042 2043-- -- Defined in Concrete.Pretty 2044-- instance Pretty a => Pretty (Named_ a) where 2045-- pretty (Named Nothing a) = pretty a 2046-- pretty (Named (Just n) a) = text (rawNameToString (rangedThing n)) <+> "=" <+> pretty a 2047 2048instance (NFData name, NFData a) => NFData (Named name a) where 2049 rnf (Named a b) = rnf a `seq` rnf b 2050 2051-- | Only 'Hidden' arguments can have names. 2052type NamedArg a = Arg (Named_ a) 2053 2054-- | Get the content of a 'NamedArg'. 2055namedArg :: NamedArg a -> a 2056namedArg = namedThing . unArg 2057 2058defaultNamedArg :: a -> NamedArg a 2059defaultNamedArg = unnamedArg defaultArgInfo 2060 2061unnamedArg :: ArgInfo -> a -> NamedArg a 2062unnamedArg info = Arg info . unnamed 2063 2064-- | The functor instance for 'NamedArg' would be ambiguous, 2065-- so we give it another name here. 2066updateNamedArg :: (a -> b) -> NamedArg a -> NamedArg b 2067updateNamedArg = fmap . fmap 2068 2069updateNamedArgA :: Applicative f => (a -> f b) -> NamedArg a -> f (NamedArg b) 2070updateNamedArgA = traverse . traverse 2071 2072-- | @setNamedArg a b = updateNamedArg (const b) a@ 2073setNamedArg :: NamedArg a -> b -> NamedArg b 2074setNamedArg a b = (b <$) <$> a 2075 2076-- ** ArgName 2077 2078-- | Names in binders and arguments. 2079type ArgName = String 2080 2081argNameToString :: ArgName -> String 2082argNameToString = id 2083 2084stringToArgName :: String -> ArgName 2085stringToArgName = id 2086 2087appendArgNames :: ArgName -> ArgName -> ArgName 2088appendArgNames = (++) 2089 2090--------------------------------------------------------------------------- 2091-- * Range decoration. 2092--------------------------------------------------------------------------- 2093 2094-- | Thing with range info. 2095data Ranged a = Ranged 2096 { rangeOf :: Range 2097 , rangedThing :: a 2098 } 2099 deriving (Data, Show, Functor, Foldable, Traversable) 2100 2101-- | Thing with no range info. 2102unranged :: a -> Ranged a 2103unranged = Ranged noRange 2104 2105-- | Ignores range. 2106instance Pretty a => Pretty (Ranged a) where 2107 pretty = pretty . rangedThing 2108 2109-- | Ignores range. 2110instance Eq a => Eq (Ranged a) where 2111 (==) = (==) `on` rangedThing 2112 2113-- | Ignores range. 2114instance Ord a => Ord (Ranged a) where 2115 compare = compare `on` rangedThing 2116 2117instance HasRange (Ranged a) where 2118 getRange = rangeOf 2119 2120instance KillRange (Ranged a) where 2121 killRange (Ranged _ x) = Ranged noRange x 2122 2123instance Decoration Ranged where 2124 traverseF f (Ranged r x) = Ranged r <$> f x 2125 2126-- | Ranges are not forced. 2127 2128instance NFData a => NFData (Ranged a) where 2129 rnf (Ranged _ a) = rnf a 2130 2131--------------------------------------------------------------------------- 2132-- * Raw names (before parsing into name parts). 2133--------------------------------------------------------------------------- 2134 2135-- | A @RawName@ is some sort of string. 2136type RawName = String 2137 2138rawNameToString :: RawName -> String 2139rawNameToString = id 2140 2141stringToRawName :: String -> RawName 2142stringToRawName = id 2143 2144-- | String with range info. 2145type RString = Ranged RawName 2146 2147--------------------------------------------------------------------------- 2148-- * Further constructor and projection info 2149--------------------------------------------------------------------------- 2150 2151-- | Where does the 'ConP' or 'Con' come from? 2152data ConOrigin 2153 = ConOSystem -- ^ Inserted by system or expanded from an implicit pattern. 2154 | ConOCon -- ^ User wrote a constructor (pattern). 2155 | ConORec -- ^ User wrote a record (pattern). 2156 | ConOSplit -- ^ Generated by interactive case splitting. 2157 deriving (Data, Show, Eq, Ord, Enum, Bounded, Generic) 2158 2159instance NFData ConOrigin 2160 2161instance KillRange ConOrigin where 2162 killRange = id 2163 2164-- | Prefer user-written over system-inserted. 2165bestConInfo :: ConOrigin -> ConOrigin -> ConOrigin 2166bestConInfo ConOSystem o = o 2167bestConInfo o _ = o 2168 2169-- | Where does a projection come from? 2170data ProjOrigin 2171 = ProjPrefix -- ^ User wrote a prefix projection. 2172 | ProjPostfix -- ^ User wrote a postfix projection. 2173 | ProjSystem -- ^ Projection was generated by the system. 2174 deriving (Data, Show, Eq, Ord, Enum, Bounded, Generic) 2175 2176instance NFData ProjOrigin 2177 2178instance KillRange ProjOrigin where 2179 killRange = id 2180 2181--------------------------------------------------------------------------- 2182-- * Infixity, access, abstract, etc. 2183--------------------------------------------------------------------------- 2184 2185-- | Functions can be defined in both infix and prefix style. See 2186-- 'Agda.Syntax.Concrete.LHS'. 2187data IsInfix = InfixDef | PrefixDef 2188 deriving (Data, Show, Eq, Ord) 2189 2190-- ** private blocks, public imports 2191 2192-- | Access modifier. 2193data Access 2194 = PrivateAccess Origin 2195 -- ^ Store the 'Origin' of the private block that lead to this qualifier. 2196 -- This is needed for more faithful printing of declarations. 2197 | PublicAccess 2198 deriving (Data, Show, Eq, Ord) 2199 2200instance Pretty Access where 2201 pretty = text . \case 2202 PrivateAccess _ -> "private" 2203 PublicAccess -> "public" 2204 2205instance NFData Access where 2206 rnf _ = () 2207 2208instance HasRange Access where 2209 getRange _ = noRange 2210 2211instance KillRange Access where 2212 killRange = id 2213 2214-- ** abstract blocks 2215 2216-- | Abstract or concrete. 2217data IsAbstract = AbstractDef | ConcreteDef 2218 deriving (Data, Show, Eq, Ord, Generic) 2219 2220-- | Semigroup computes if any of several is an 'AbstractDef'. 2221instance Semigroup IsAbstract where 2222 AbstractDef <> _ = AbstractDef 2223 ConcreteDef <> a = a 2224 2225-- | Default is 'ConcreteDef'. 2226instance Monoid IsAbstract where 2227 mempty = ConcreteDef 2228 mappend = (<>) 2229 2230instance KillRange IsAbstract where 2231 killRange = id 2232 2233instance NFData IsAbstract 2234 2235class LensIsAbstract a where 2236 lensIsAbstract :: Lens' IsAbstract a 2237 2238instance LensIsAbstract IsAbstract where 2239 lensIsAbstract = id 2240 2241-- | Is any element of a collection an 'AbstractDef'. 2242class AnyIsAbstract a where 2243 anyIsAbstract :: a -> IsAbstract 2244 2245 default anyIsAbstract :: (Foldable t, AnyIsAbstract b, t b ~ a) => a -> IsAbstract 2246 anyIsAbstract = Fold.foldMap anyIsAbstract 2247 2248instance AnyIsAbstract IsAbstract where 2249 anyIsAbstract = id 2250 2251instance AnyIsAbstract a => AnyIsAbstract [a] where 2252instance AnyIsAbstract a => AnyIsAbstract (Maybe a) where 2253 2254-- ** instance blocks 2255 2256-- | Is this definition eligible for instance search? 2257data IsInstance 2258 = InstanceDef Range -- ^ Range of the @instance@ keyword. 2259 | NotInstanceDef 2260 deriving (Data, Show, Eq, Ord) 2261 2262instance KillRange IsInstance where 2263 killRange = \case 2264 InstanceDef _ -> InstanceDef noRange 2265 i@NotInstanceDef -> i 2266 2267instance HasRange IsInstance where 2268 getRange = \case 2269 InstanceDef r -> r 2270 NotInstanceDef -> noRange 2271 2272instance NFData IsInstance where 2273 rnf (InstanceDef _) = () 2274 rnf NotInstanceDef = () 2275 2276-- ** macro blocks 2277 2278-- | Is this a macro definition? 2279data IsMacro = MacroDef | NotMacroDef 2280 deriving (Data, Show, Eq, Ord, Generic) 2281 2282instance KillRange IsMacro where killRange = id 2283instance HasRange IsMacro where getRange _ = noRange 2284 2285instance NFData IsMacro 2286 2287--------------------------------------------------------------------------- 2288-- * NameId 2289--------------------------------------------------------------------------- 2290 2291newtype ModuleNameHash = ModuleNameHash Word64 2292 deriving (Eq, Ord, Show, Data) 2293 2294noModuleNameHash :: ModuleNameHash 2295noModuleNameHash = ModuleNameHash 0 2296 2297-- | The unique identifier of a name. Second argument is the top-level module 2298-- identifier. 2299data NameId = NameId {-# UNPACK #-} !Word64 {-# UNPACK #-} !ModuleNameHash 2300 deriving (Eq, Ord, Data, Generic, Show) 2301 2302instance KillRange NameId where 2303 killRange = id 2304 2305instance Pretty NameId where 2306 pretty (NameId n m) = text $ show n ++ "@" ++ show m 2307 2308instance Enum NameId where 2309 succ (NameId n m) = NameId (n + 1) m 2310 pred (NameId n m) = NameId (n - 1) m 2311 toEnum n = __IMPOSSIBLE__ -- should not be used 2312 fromEnum (NameId n _) = fromIntegral n 2313 2314instance NFData NameId where 2315 rnf (NameId _ _) = () 2316 2317instance NFData ModuleNameHash where 2318 rnf _ = () 2319 2320instance Hashable NameId where 2321 {-# INLINE hashWithSalt #-} 2322 hashWithSalt salt (NameId n (ModuleNameHash m)) = hashWithSalt salt (n, m) 2323 2324--------------------------------------------------------------------------- 2325-- * Meta variables 2326--------------------------------------------------------------------------- 2327 2328-- | A meta variable identifier is just a natural number. 2329-- 2330newtype MetaId = MetaId { metaId :: Nat } 2331 deriving (Eq, Ord, Num, Real, Enum, Integral, Data, Generic) 2332 2333instance Pretty MetaId where 2334 pretty (MetaId n) = text $ "_" ++ show n 2335 2336-- | Show non-record version of this newtype. 2337instance Show MetaId where 2338 showsPrec p (MetaId n) = showParen (p > 0) $ 2339 showString "MetaId " . shows n 2340 2341instance NFData MetaId where 2342 rnf (MetaId x) = rnf x 2343 2344instance Hashable MetaId 2345 2346newtype Constr a = Constr a 2347 2348----------------------------------------------------------------------------- 2349-- * Problems 2350----------------------------------------------------------------------------- 2351 2352-- | A "problem" consists of a set of constraints and the same constraint can be part of multiple 2353-- problems. 2354newtype ProblemId = ProblemId Nat 2355 deriving (Data, Eq, Ord, Enum, Real, Integral, Num, NFData) 2356 2357-- This particular Show instance is ok because of the Num instance. 2358instance Show ProblemId where show (ProblemId n) = show n 2359instance Pretty ProblemId where pretty (ProblemId n) = pretty n 2360 2361------------------------------------------------------------------------ 2362-- * Placeholders (used to parse sections) 2363------------------------------------------------------------------------ 2364 2365-- | The position of a name part or underscore in a name. 2366 2367data PositionInName 2368 = Beginning 2369 -- ^ The following underscore is at the beginning of the name: 2370 -- @_foo@. 2371 | Middle 2372 -- ^ The following underscore is in the middle of the name: 2373 -- @foo_bar@. 2374 | End 2375 -- ^ The following underscore is at the end of the name: @foo_@. 2376 deriving (Show, Eq, Ord, Data) 2377 2378-- | Placeholders are used to represent the underscores in a section. 2379 2380data MaybePlaceholder e 2381 = Placeholder !PositionInName 2382 | NoPlaceholder !(Strict.Maybe PositionInName) e 2383 -- ^ The second argument is used only (but not always) for name 2384 -- parts other than underscores. 2385 deriving (Data, Eq, Ord, Functor, Foldable, Traversable, Show) 2386 2387-- | An abbreviation: @noPlaceholder = 'NoPlaceholder' 2388-- 'Strict.Nothing'@. 2389 2390noPlaceholder :: e -> MaybePlaceholder e 2391noPlaceholder = NoPlaceholder Strict.Nothing 2392 2393instance HasRange a => HasRange (MaybePlaceholder a) where 2394 getRange Placeholder{} = noRange 2395 getRange (NoPlaceholder _ e) = getRange e 2396 2397instance KillRange a => KillRange (MaybePlaceholder a) where 2398 killRange p@Placeholder{} = p 2399 killRange (NoPlaceholder p e) = killRange1 (NoPlaceholder p) e 2400 2401instance NFData a => NFData (MaybePlaceholder a) where 2402 rnf (Placeholder _) = () 2403 rnf (NoPlaceholder _ a) = rnf a 2404 2405--------------------------------------------------------------------------- 2406-- * Interaction meta variables 2407--------------------------------------------------------------------------- 2408 2409newtype InteractionId = InteractionId { interactionId :: Nat } 2410 deriving ( Eq 2411 , Ord 2412 , Show 2413 , Num 2414 , Integral 2415 , Real 2416 , Enum 2417 , Data 2418 , NFData 2419 ) 2420 2421instance Pretty InteractionId where 2422 pretty (InteractionId i) = text $ "?" ++ show i 2423 2424instance KillRange InteractionId where killRange = id 2425 2426--------------------------------------------------------------------------- 2427-- * Fixity 2428--------------------------------------------------------------------------- 2429 2430-- | Precedence levels for operators. 2431 2432type PrecedenceLevel = Double 2433 2434data FixityLevel 2435 = Unrelated 2436 -- ^ No fixity declared. 2437 | Related !PrecedenceLevel 2438 -- ^ Fixity level declared as the number. 2439 deriving (Eq, Ord, Show, Data) 2440 2441instance Null FixityLevel where 2442 null Unrelated = True 2443 null Related{} = False 2444 empty = Unrelated 2445 2446instance NFData FixityLevel where 2447 rnf Unrelated = () 2448 rnf (Related _) = () 2449 2450-- | Associativity. 2451 2452data Associativity = NonAssoc | LeftAssoc | RightAssoc 2453 deriving (Eq, Ord, Show, Data) 2454 2455-- | Fixity of operators. 2456 2457data Fixity = Fixity 2458 { fixityRange :: Range 2459 -- ^ Range of the whole fixity declaration. 2460 , fixityLevel :: !FixityLevel 2461 , fixityAssoc :: !Associativity 2462 } 2463 deriving (Data, Show) 2464 2465noFixity :: Fixity 2466noFixity = Fixity noRange Unrelated NonAssoc 2467 2468defaultFixity :: Fixity 2469defaultFixity = Fixity noRange (Related 20) NonAssoc 2470 2471-- For @instance Pretty Fixity@, see Agda.Syntax.Concrete.Pretty 2472 2473instance Eq Fixity where 2474 f1 == f2 = compare f1 f2 == EQ 2475 2476instance Ord Fixity where 2477 compare = compare `on` (fixityLevel &&& fixityAssoc) 2478 2479instance Null Fixity where 2480 null = null . fixityLevel 2481 empty = noFixity 2482 2483instance HasRange Fixity where 2484 getRange = fixityRange 2485 2486instance KillRange Fixity where 2487 killRange f = f { fixityRange = noRange } 2488 2489instance NFData Fixity where 2490 rnf (Fixity _ _ _) = () -- Ranges are not forced, the other fields are strict. 2491 2492-- * Notation coupled with 'Fixity' 2493 2494-- | The notation is handled as the fixity in the renamer. 2495-- Hence, they are grouped together in this type. 2496data Fixity' = Fixity' 2497 { theFixity :: !Fixity 2498 , theNotation :: Notation 2499 , theNameRange :: Range 2500 -- ^ Range of the name in the fixity declaration 2501 -- (used for correct highlighting, see issue #2140). 2502 } 2503 deriving (Data, Show) 2504 2505noFixity' :: Fixity' 2506noFixity' = Fixity' noFixity noNotation noRange 2507 2508instance Eq Fixity' where 2509 Fixity' f n _ == Fixity' f' n' _ = f == f' && n == n' 2510 2511instance Null Fixity' where 2512 null (Fixity' f n _) = null f && null n 2513 empty = noFixity' 2514 2515instance NFData Fixity' where 2516 rnf (Fixity' _ a _) = rnf a 2517 2518instance KillRange Fixity' where 2519 killRange (Fixity' f n r) = killRange3 Fixity' f n r 2520 2521-- lenses 2522 2523_fixityAssoc :: Lens' Associativity Fixity 2524_fixityAssoc f r = f (fixityAssoc r) <&> \x -> r { fixityAssoc = x } 2525 2526_fixityLevel :: Lens' FixityLevel Fixity 2527_fixityLevel f r = f (fixityLevel r) <&> \x -> r { fixityLevel = x } 2528 2529-- Lens focusing on Fixity 2530 2531class LensFixity a where 2532 lensFixity :: Lens' Fixity a 2533 2534instance LensFixity Fixity where 2535 lensFixity = id 2536 2537instance LensFixity Fixity' where 2538 lensFixity f fix' = f (theFixity fix') <&> \ fx -> fix' { theFixity = fx } 2539 2540-- Lens focusing on Fixity' 2541 2542class LensFixity' a where 2543 lensFixity' :: Lens' Fixity' a 2544 2545instance LensFixity' Fixity' where 2546 lensFixity' = id 2547--------------------------------------------------------------------------- 2548-- * Import directive 2549--------------------------------------------------------------------------- 2550 2551-- | The things you are allowed to say when you shuffle names between name 2552-- spaces (i.e. in @import@, @namespace@, or @open@ declarations). 2553data ImportDirective' n m = ImportDirective 2554 { importDirRange :: Range 2555 , using :: Using' n m 2556 , hiding :: HidingDirective' n m 2557 , impRenaming :: RenamingDirective' n m 2558 , publicOpen :: Maybe Range -- ^ Only for @open@. Exports the opened names from the current module. 2559 } 2560 deriving (Data, Eq) 2561 2562type HidingDirective' n m = [ImportedName' n m] 2563type RenamingDirective' n m = [Renaming' n m] 2564 2565-- | @null@ for import directives holds when everything is imported unchanged 2566-- (no names are hidden or renamed). 2567instance Null (ImportDirective' n m) where 2568 null = \case 2569 ImportDirective _ UseEverything [] [] _ -> True 2570 _ -> False 2571 empty = defaultImportDir 2572 2573instance (HasRange n, HasRange m) => Semigroup (ImportDirective' n m) where 2574 i1 <> i2 = ImportDirective 2575 { importDirRange = fuseRange i1 i2 2576 , using = using i1 <> using i2 2577 , hiding = hiding i1 ++ hiding i2 2578 , impRenaming = impRenaming i1 ++ impRenaming i2 2579 , publicOpen = publicOpen i1 <|> publicOpen i2 2580 } 2581 2582instance (HasRange n, HasRange m) => Monoid (ImportDirective' n m) where 2583 mempty = empty 2584 mappend = (<>) 2585 2586-- | Default is directive is @private@ (use everything, but do not export). 2587defaultImportDir :: ImportDirective' n m 2588defaultImportDir = ImportDirective noRange UseEverything [] [] Nothing 2589 2590-- | @isDefaultImportDir@ implies @null@, but not the other way round. 2591isDefaultImportDir :: ImportDirective' n m -> Bool 2592isDefaultImportDir dir = null dir && null (publicOpen dir) 2593 2594-- | The @using@ clause of import directive. 2595data Using' n m 2596 = UseEverything -- ^ No @using@ clause given. 2597 | Using [ImportedName' n m] -- ^ @using@ the specified names. 2598 deriving (Data, Eq) 2599 2600instance Semigroup (Using' n m) where 2601 UseEverything <> u = u 2602 u <> UseEverything = u 2603 Using xs <> Using ys = Using (xs ++ ys) 2604 2605instance Monoid (Using' n m) where 2606 mempty = UseEverything 2607 mappend = (<>) 2608 2609instance Null (Using' n m) where 2610 null UseEverything = True 2611 null Using{} = False 2612 empty = mempty 2613 2614mapUsing :: ([ImportedName' n1 m1] -> [ImportedName' n2 m2]) -> Using' n1 m1 -> Using' n2 m2 2615mapUsing f = \case 2616 UseEverything -> UseEverything 2617 Using xs -> Using $ f xs 2618 2619-- | An imported name can be a module or a defined name. 2620data ImportedName' n m 2621 = ImportedModule m -- ^ Imported module name of type @m@. 2622 | ImportedName n -- ^ Imported name of type @n@. 2623 deriving (Data, Eq, Ord, Show) 2624 2625fromImportedName :: ImportedName' a a -> a 2626fromImportedName = \case 2627 ImportedModule x -> x 2628 ImportedName x -> x 2629 2630setImportedName :: ImportedName' a a -> a -> ImportedName' a a 2631setImportedName (ImportedName x) y = ImportedName y 2632setImportedName (ImportedModule x) y = ImportedModule y 2633 2634-- | Like 'partitionEithers'. 2635partitionImportedNames :: [ImportedName' n m] -> ([n], [m]) 2636partitionImportedNames = flip foldr ([], []) $ \case 2637 ImportedName n -> first (n:) 2638 ImportedModule m -> second (m:) 2639 2640-- -- Defined in Concrete.Pretty 2641-- instance (Pretty n, Pretty m) => Pretty (ImportedName' n m) where 2642-- pretty (ImportedModule x) = "module" <+> pretty x 2643-- pretty (ImportedName x) = pretty x 2644 2645-- instance (Show n, Show m) => Show (ImportedName' n m) where 2646-- show (ImportedModule x) = "module " ++ show x 2647-- show (ImportedName x) = show x 2648 2649data Renaming' n m = Renaming 2650 { renFrom :: ImportedName' n m 2651 -- ^ Rename from this name. 2652 , renTo :: ImportedName' n m 2653 -- ^ To this one. Must be same kind as 'renFrom'. 2654 , renFixity :: Maybe Fixity 2655 -- ^ New fixity of 'renTo' (optional). 2656 , renToRange :: Range 2657 -- ^ The range of the \"to\" keyword. Retained for highlighting purposes. 2658 } 2659 deriving (Data, Eq) 2660 2661-- ** HasRange instances 2662 2663instance (HasRange a, HasRange b) => HasRange (ImportDirective' a b) where 2664 getRange = importDirRange 2665 2666instance (HasRange a, HasRange b) => HasRange (Using' a b) where 2667 getRange (Using xs) = getRange xs 2668 getRange UseEverything = noRange 2669 2670instance (HasRange a, HasRange b) => HasRange (Renaming' a b) where 2671 getRange r = getRange (renFrom r, renTo r) 2672 2673instance (HasRange a, HasRange b) => HasRange (ImportedName' a b) where 2674 getRange (ImportedName x) = getRange x 2675 getRange (ImportedModule x) = getRange x 2676 2677-- ** KillRange instances 2678 2679instance (KillRange a, KillRange b) => KillRange (ImportDirective' a b) where 2680 killRange (ImportDirective _ u h r p) = 2681 killRange3 (\u h r -> ImportDirective noRange u h r p) u h r 2682 2683instance (KillRange a, KillRange b) => KillRange (Using' a b) where 2684 killRange (Using i) = killRange1 Using i 2685 killRange UseEverything = UseEverything 2686 2687instance (KillRange a, KillRange b) => KillRange (Renaming' a b) where 2688 killRange (Renaming i n mf _to) = killRange3 (\ i n mf -> Renaming i n mf noRange) i n mf 2689 2690instance (KillRange a, KillRange b) => KillRange (ImportedName' a b) where 2691 killRange (ImportedModule n) = killRange1 ImportedModule n 2692 killRange (ImportedName n) = killRange1 ImportedName n 2693 2694-- ** NFData instances 2695 2696-- | Ranges are not forced. 2697 2698instance (NFData a, NFData b) => NFData (ImportDirective' a b) where 2699 rnf (ImportDirective _ a b c _) = rnf a `seq` rnf b `seq` rnf c 2700 2701instance (NFData a, NFData b) => NFData (Using' a b) where 2702 rnf UseEverything = () 2703 rnf (Using a) = rnf a 2704 2705-- | Ranges are not forced. 2706 2707instance (NFData a, NFData b) => NFData (Renaming' a b) where 2708 rnf (Renaming a b c _) = rnf a `seq` rnf b `seq` rnf c 2709 2710instance (NFData a, NFData b) => NFData (ImportedName' a b) where 2711 rnf (ImportedModule a) = rnf a 2712 rnf (ImportedName a) = rnf a 2713 2714----------------------------------------------------------------------------- 2715-- * Termination 2716----------------------------------------------------------------------------- 2717 2718-- | Termination check? (Default = TerminationCheck). 2719data TerminationCheck m 2720 = TerminationCheck 2721 -- ^ Run the termination checker. 2722 | NoTerminationCheck 2723 -- ^ Skip termination checking (unsafe). 2724 | NonTerminating 2725 -- ^ Treat as non-terminating. 2726 | Terminating 2727 -- ^ Treat as terminating (unsafe). Same effect as 'NoTerminationCheck'. 2728 | TerminationMeasure Range m 2729 -- ^ Skip termination checking but use measure instead. 2730 deriving (Data, Show, Eq, Functor) 2731 2732instance KillRange m => KillRange (TerminationCheck m) where 2733 killRange (TerminationMeasure _ m) = TerminationMeasure noRange (killRange m) 2734 killRange t = t 2735 2736instance NFData a => NFData (TerminationCheck a) where 2737 rnf TerminationCheck = () 2738 rnf NoTerminationCheck = () 2739 rnf NonTerminating = () 2740 rnf Terminating = () 2741 rnf (TerminationMeasure _ a) = rnf a 2742 2743----------------------------------------------------------------------------- 2744-- * Positivity 2745----------------------------------------------------------------------------- 2746 2747-- | Positivity check? (Default = True). 2748data PositivityCheck = YesPositivityCheck | NoPositivityCheck 2749 deriving (Eq, Ord, Show, Bounded, Enum, Data, Generic) 2750 2751instance KillRange PositivityCheck where 2752 killRange = id 2753 2754-- Semigroup and Monoid via conjunction 2755instance Semigroup PositivityCheck where 2756 NoPositivityCheck <> _ = NoPositivityCheck 2757 _ <> NoPositivityCheck = NoPositivityCheck 2758 _ <> _ = YesPositivityCheck 2759 2760instance Monoid PositivityCheck where 2761 mempty = YesPositivityCheck 2762 mappend = (<>) 2763 2764instance NFData PositivityCheck 2765 2766----------------------------------------------------------------------------- 2767-- * Universe checking 2768----------------------------------------------------------------------------- 2769 2770-- | Universe check? (Default is yes). 2771data UniverseCheck = YesUniverseCheck | NoUniverseCheck 2772 deriving (Eq, Ord, Show, Bounded, Enum, Data, Generic) 2773 2774instance KillRange UniverseCheck where 2775 killRange = id 2776 2777instance NFData UniverseCheck 2778 2779----------------------------------------------------------------------------- 2780-- * Universe checking 2781----------------------------------------------------------------------------- 2782 2783-- | Coverage check? (Default is yes). 2784data CoverageCheck = YesCoverageCheck | NoCoverageCheck 2785 deriving (Eq, Ord, Show, Bounded, Enum, Data, Generic) 2786 2787instance KillRange CoverageCheck where 2788 killRange = id 2789 2790-- Semigroup and Monoid via conjunction 2791instance Semigroup CoverageCheck where 2792 NoCoverageCheck <> _ = NoCoverageCheck 2793 _ <> NoCoverageCheck = NoCoverageCheck 2794 _ <> _ = YesCoverageCheck 2795 2796instance Monoid CoverageCheck where 2797 mempty = YesCoverageCheck 2798 mappend = (<>) 2799 2800instance NFData CoverageCheck 2801 2802----------------------------------------------------------------------------- 2803-- * Rewrite Directives on the LHS 2804----------------------------------------------------------------------------- 2805 2806-- | @RewriteEqn' qn p e@ represents the @rewrite@ and irrefutable @with@ 2807-- clauses of the LHS. 2808-- @qn@ stands for the QName of the auxiliary function generated to implement the feature 2809-- @nm@ is the type of names for pattern variables 2810-- @p@ is the type of patterns 2811-- @e@ is the type of expressions 2812 2813data RewriteEqn' qn nm p e 2814 = Rewrite (List1 (qn, e)) -- ^ @rewrite e@ 2815 | Invert qn (List1 (Named nm (p, e))) -- ^ @with p <- e in eq@ 2816 deriving (Data, Eq, Show, Functor, Foldable, Traversable) 2817 2818instance (NFData qn, NFData nm, NFData p, NFData e) => NFData (RewriteEqn' qn nm p e) where 2819 rnf = \case 2820 Rewrite es -> rnf es 2821 Invert qn pes -> rnf (qn, pes) 2822 2823instance (Pretty nm, Pretty p, Pretty e) => Pretty (RewriteEqn' qn nm p e) where 2824 pretty = \case 2825 Rewrite es -> prefixedThings (text "rewrite") $ List1.toList (pretty . snd <$> es) 2826 Invert _ pes -> prefixedThings (text "invert") $ List1.toList (namedWith <$> pes) where 2827 2828 namedWith (Named nm (p, e)) = 2829 let patexp = pretty p <+> "<-" <+> pretty e in 2830 case nm of 2831 Nothing -> patexp 2832 Just nm -> pretty nm <+> ":" <+> patexp 2833 2834instance (HasRange qn, HasRange nm, HasRange p, HasRange e) => HasRange (RewriteEqn' qn nm p e) where 2835 getRange = \case 2836 Rewrite es -> getRange es 2837 Invert qn pes -> getRange (qn, pes) 2838 2839instance (KillRange qn, KillRange nm, KillRange e, KillRange p) => KillRange (RewriteEqn' qn nm p e) where 2840 killRange = \case 2841 Rewrite es -> killRange1 Rewrite es 2842 Invert qn pes -> killRange2 Invert qn pes 2843 2844----------------------------------------------------------------------------- 2845-- * Information on expanded ellipsis (@...@) 2846----------------------------------------------------------------------------- 2847 2848-- ^ When the ellipsis in a clause is expanded, we remember that we 2849-- did so. We also store the number of with-arguments that are 2850-- included in the expanded ellipsis. 2851data ExpandedEllipsis 2852 = ExpandedEllipsis 2853 { ellipsisRange :: Range 2854 , ellipsisWithArgs :: Int 2855 } 2856 | NoEllipsis 2857 deriving (Data, Show, Eq) 2858 2859instance Null ExpandedEllipsis where 2860 null = (== NoEllipsis) 2861 empty = NoEllipsis 2862 2863instance KillRange ExpandedEllipsis where 2864 killRange (ExpandedEllipsis _ k) = ExpandedEllipsis noRange k 2865 killRange NoEllipsis = NoEllipsis 2866 2867instance NFData ExpandedEllipsis where 2868 rnf (ExpandedEllipsis _ a) = rnf a 2869 rnf NoEllipsis = () 2870 2871-- | Notation as provided by the @syntax@ declaration. 2872type Notation = [GenPart] 2873 2874noNotation :: Notation 2875noNotation = [] 2876 2877-- | Part of a Notation 2878data GenPart 2879 = BindHole Range (Ranged Int) 2880 -- ^ Argument is the position of the hole (with binding) where the binding should occur. 2881 -- First range is the rhs range and second is the binder. 2882 | NormalHole Range (NamedArg (Ranged Int)) 2883 -- ^ Argument is where the expression should go. 2884 | WildHole (Ranged Int) 2885 -- ^ An underscore in binding position. 2886 | IdPart RString 2887 deriving (Data, Show) 2888 2889instance Eq GenPart where 2890 BindHole _ i == BindHole _ j = i == j 2891 NormalHole _ x == NormalHole _ y = x == y 2892 WildHole i == WildHole j = i == j 2893 IdPart x == IdPart y = x == y 2894 _ == _ = False 2895 2896instance Ord GenPart where 2897 BindHole _ i `compare` BindHole _ j = i `compare` j 2898 NormalHole _ x `compare` NormalHole _ y = x `compare` y 2899 WildHole i `compare` WildHole j = i `compare` j 2900 IdPart x `compare` IdPart y = x `compare` y 2901 BindHole{} `compare` _ = LT 2902 _ `compare` BindHole{} = GT 2903 NormalHole{} `compare` _ = LT 2904 _ `compare` NormalHole{} = GT 2905 WildHole{} `compare` _ = LT 2906 _ `compare` WildHole{} = GT 2907 2908instance HasRange GenPart where 2909 getRange = \case 2910 IdPart x -> getRange x 2911 BindHole r _ -> r 2912 WildHole i -> getRange i 2913 NormalHole r _ -> r 2914 2915instance SetRange GenPart where 2916 setRange r = \case 2917 IdPart x -> IdPart x 2918 BindHole _ i -> BindHole r i 2919 WildHole i -> WildHole i 2920 NormalHole _ i -> NormalHole r i 2921 2922instance KillRange GenPart where 2923 killRange = \case 2924 IdPart x -> IdPart $ killRange x 2925 BindHole _ i -> BindHole noRange $ killRange i 2926 WildHole i -> WildHole $ killRange i 2927 NormalHole _ x -> NormalHole noRange $ killRange x 2928 2929instance NFData GenPart where 2930 rnf (BindHole _ a) = rnf a 2931 rnf (NormalHole _ a) = rnf a 2932 rnf (WildHole a) = rnf a 2933 rnf (IdPart a) = rnf a 2934