-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A dependently typed functional programming language and proof assistant -- -- Agda is a dependently typed functional programming language: It has -- inductive families, which are similar to Haskell's GADTs, but they can -- be indexed by values and not just types. It also has parameterised -- modules, mixfix operators, Unicode characters, and an interactive -- Emacs interface (the type checker can assist in the development of -- your code). -- -- Agda is also a proof assistant: It is an interactive system for -- writing and checking proofs. Agda is based on intuitionistic type -- theory, a foundational system for constructive mathematics developed -- by the Swedish logician Per Martin-Löf. It has many similarities with -- other proof assistants based on dependent types, such as Coq, Epigram -- and NuPRL. -- -- This package includes both a command-line program (agda) and an Emacs -- mode. If you want to use the Emacs mode you can set it up by running -- agda-mode setup (see the README). -- -- Note that the Agda library does not follow the package versioning -- policy, because it is not intended to be used by third-party packages. @package Agda @version 2.4.2.5 -- | Utilities for Data.IORef. module Agda.Utils.IORef -- | Read IORef, modify it strictly, and return old value. readModifyIORef' :: IORef a -> (a -> a) -> IO a module Agda.Utils.SemiRing -- | Semirings (https://en.wikipedia.org/wiki/Semiring). class SemiRing a ozero :: SemiRing a => a oone :: SemiRing a => a oplus :: SemiRing a => a -> a -> a otimes :: SemiRing a => a -> a -> a -- | Star semirings -- (https://en.wikipedia.org/wiki/Semiring#Star_semirings). class SemiRing a => StarSemiRing a ostar :: StarSemiRing a => a -> a instance Agda.Utils.SemiRing.SemiRing a => Agda.Utils.SemiRing.SemiRing (GHC.Base.Maybe a) instance Agda.Utils.SemiRing.StarSemiRing a => Agda.Utils.SemiRing.StarSemiRing (GHC.Base.Maybe a) -- | Create clusters of non-overlapping things. module Agda.Utils.Cluster -- | Given a function f :: a -> (C,[C]) which returns a -- non-empty list of characteristics C of a, partition -- a list of as into groups such that each element in a group -- shares at least one characteristic with at least one other element of -- the group. cluster :: (a -> (C, [C])) -> [a] -> [[a]] -- | Partition a list of as paired with a non-empty list of -- characteristics $C$ into groups such that each element in a group -- shares at least one characteristic with at least one other element of -- the group. cluster' :: [(a, (C, [C]))] -> [[a]] tests :: IO Bool -- | Finite bijections (implemented as a pair of maps). module Agda.Utils.BiMap -- | Finite bijective map from a to b. There, and back -- again. data BiMap a b BiMap :: Map a b -> Map b a -> BiMap a b [biMapThere] :: BiMap a b -> Map a b [biMapBack] :: BiMap a b -> Map b a -- | Lookup. O(log n). lookup :: (Ord a, Ord b) => a -> BiMap a b -> Maybe b -- | Inverse lookup. O(log n). invLookup :: (Ord a, Ord b) => b -> BiMap a b -> Maybe a -- | Empty bimap. O(1). empty :: (Ord a, Ord b) => BiMap a b -- | Singleton bimap. O(1). singleton :: (Ord a, Ord b) => a -> b -> BiMap a b -- | Insert. Overwrites existing value if present. insert :: (Ord a, Ord b) => a -> b -> BiMap a b -> BiMap a b -- | Left-biased Union. O(Map.union). union :: (Ord a, Ord b) => BiMap a b -> BiMap a b -> BiMap a b -- | Construct from a list of pairs. -- -- Does not check for actual bijectivity of constructed finite map. fromList :: (Ord a, Ord b) => [(a, b)] -> BiMap a b -- | Turn into list, sorted ascendingly by first value. toList :: (Ord a, Ord b) => BiMap a b -> [(a, b)] prop_BiMap_invariant :: (Ord a, Ord b) => BiMap a b -> Bool tests :: IO Bool instance (GHC.Classes.Ord a, GHC.Classes.Ord b) => GHC.Classes.Eq (Agda.Utils.BiMap.BiMap a b) instance (GHC.Classes.Ord a, GHC.Classes.Ord b) => GHC.Classes.Ord (Agda.Utils.BiMap.BiMap a b) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Classes.Ord a, GHC.Classes.Ord b) => GHC.Show.Show (Agda.Utils.BiMap.BiMap a b) instance (GHC.Classes.Ord a, GHC.Classes.Ord b, Test.QuickCheck.Arbitrary.Arbitrary a, Test.QuickCheck.Arbitrary.Arbitrary b) => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Utils.BiMap.BiMap a b) -- | Var field implementation of sets of (small) natural numbers. module Agda.Utils.VarSet type VarSet = IntSet -- | O(n+m). The union of two sets. union :: IntSet -> IntSet -> IntSet -- | The union of a list of sets. unions :: [IntSet] -> IntSet -- | O(min(n,W)). Is the value a member of the set? member :: Key -> IntSet -> Bool -- | O(1). The empty set. empty :: IntSet -- | O(min(n,W)). Delete a value in the set. Returns the original -- set when the value was not present. delete :: Key -> IntSet -> IntSet -- | O(1). A set of one element. singleton :: Key -> IntSet -- | O(n*min(n,W)). Create a set from a list of integers. fromList :: [Key] -> IntSet -- | O(n). Convert the set to a list of elements. Subject to list -- fusion. toList :: IntSet -> [Key] -- | O(n). Convert the set to a descending list of elements. Subject -- to list fusion. toDescList :: IntSet -> [Key] -- | O(n+m). Is this a subset? (s1 isSubsetOf s2) -- tells whether s1 is a subset of s2. isSubsetOf :: IntSet -> IntSet -> Bool -- | O(1). Is the set empty? null :: IntSet -> Bool -- | O(n+m). The intersection of two sets. intersection :: IntSet -> IntSet -> IntSet -- | O(n+m). Difference between two sets. difference :: IntSet -> IntSet -> IntSet subtract :: Int -> VarSet -> VarSet module Agda.Utils.Char -- | Convert a character in '0'..'9' into the corresponding digit -- 0..9. decDigit :: Char -> Int -- | Convert a character in '0'..'9','A'..'F','a'..'f' into the -- corresponding digit 0..15. hexDigit :: Char -> Int -- | Convert a character in '0'..'7' into the corresponding digit -- 0..7. octDigit :: Char -> Int -- | Unicode characters are divided into letters, numbers, marks, -- punctuation, symbols, separators (including spaces) and others -- (including control characters). -- -- These are the tests that Char offers data UnicodeTest IsControl :: UnicodeTest IsSpace :: UnicodeTest IsLower :: UnicodeTest IsUpper :: UnicodeTest IsAlpha :: UnicodeTest IsAlphaNum :: UnicodeTest IsPrint :: UnicodeTest IsDigit :: UnicodeTest IsOctDigit :: UnicodeTest IsHexDigit :: UnicodeTest IsLetter :: UnicodeTest IsMark :: UnicodeTest IsNumber :: UnicodeTest IsPunctuation :: UnicodeTest IsSymbol :: UnicodeTest IsSeparator :: UnicodeTest -- | Test names paired with their implementation. unicodeTests :: [(UnicodeTest, Char -> Bool)] -- | Find out which tests a character satisfies. testChar :: Char -> [UnicodeTest] instance GHC.Show.Show Agda.Utils.Char.UnicodeTest instance GHC.Classes.Ord Agda.Utils.Char.UnicodeTest instance GHC.Classes.Eq Agda.Utils.Char.UnicodeTest module Agda.Utils.Pointer data Ptr a newPtr :: a -> Ptr a derefPtr :: Ptr a -> a setPtr :: a -> Ptr a -> Ptr a updatePtr :: (a -> a) -> Ptr a -> Ptr a -- | If f a contains many copies of a they will all be -- the same pointer in the result. If the function is well-behaved (i.e. -- preserves the implicit equivalence, this shouldn't matter). updatePtrM :: Functor f => (a -> f a) -> Ptr a -> f (Ptr a) instance GHC.Show.Show a => GHC.Show.Show (Agda.Utils.Pointer.Ptr a) instance GHC.Base.Functor Agda.Utils.Pointer.Ptr instance Data.Foldable.Foldable Agda.Utils.Pointer.Ptr instance Data.Traversable.Traversable Agda.Utils.Pointer.Ptr instance GHC.Classes.Eq (Agda.Utils.Pointer.Ptr a) instance GHC.Classes.Ord (Agda.Utils.Pointer.Ptr a) instance Data.Hashable.Class.Hashable (Agda.Utils.Pointer.Ptr a) instance Control.DeepSeq.NFData (Agda.Utils.Pointer.Ptr a) -- | Defines CutOff type which is used in -- Agda.Interaction.Options. This module's purpose is to eliminate -- the dependency of Agda.TypeChecking.Monad.Base on the -- termination checker and everything it imports. module Agda.Termination.CutOff -- | Cut off structural order comparison at some depth in termination -- checker? data CutOff -- | c >= 0 means: record decrease up to including -- c+1. CutOff :: Int -> CutOff DontCutOff :: CutOff instance GHC.Classes.Ord Agda.Termination.CutOff.CutOff instance GHC.Classes.Eq Agda.Termination.CutOff.CutOff instance GHC.Show.Show Agda.Termination.CutOff.CutOff -- | Binary IO. module Agda.Utils.IO.Binary -- | Returns a close function for the file together with the contents. readBinaryFile' :: FilePath -> IO (ByteString, IO ()) -- | Some functions and generators suitable for writing QuickCheck -- properties. module Agda.Utils.TestHelpers -- | Is the operator associative? associative :: (Arbitrary a, Eq a, Show a) => (a -> a -> a) -> a -> a -> a -> Bool -- | Is the operator commutative? commutative :: (Arbitrary a, Eq a, Show a) => (a -> a -> a) -> a -> a -> Bool -- | Is the operator idempotent? idempotent :: (Arbitrary a, Eq a, Show a) => (a -> a -> a) -> a -> Bool -- | Is the element a zero for the operator? isZero :: (Arbitrary a, Eq a, Show a) => a -> (a -> a -> a) -> a -> Bool -- | Is the element a unit for the operator? identity :: (Arbitrary a, Eq a, Show a) => a -> (a -> a -> a) -> a -> Bool -- | Does the first operator distribute (from the left) over the second -- one? leftDistributive :: (Arbitrary a, Eq a, Show a) => (a -> a -> a) -> (a -> a -> a) -> a -> a -> a -> Bool -- | Does the first operator distribute (from the right) over the second -- one? rightDistributive :: (Arbitrary a, Eq a, Show a) => (a -> a -> a) -> (a -> a -> a) -> a -> a -> a -> Bool -- | Does the first operator distribute over the second one? distributive :: (Arbitrary a, Eq a, Show a) => (a -> a -> a) -> (a -> a -> a) -> a -> a -> a -> Bool -- | Generates natural numbers. natural :: (Integral i) => Gen i -- | Generates positive numbers. positive :: (Integral i) => Gen i -- | Generates values of Maybe type, using the given generator to -- generate the contents of the Just constructor. maybeGen :: Gen a -> Gen (Maybe a) -- | Coarbitrary "generator" for Maybe. maybeCoGen :: (a -> Gen b -> Gen b) -> (Maybe a -> Gen b -> Gen b) -- | Generates a list of elements picked from a given list. listOfElements :: [a] -> Gen [a] -- | If the given list is non-empty, then an element from the list is -- generated, and otherwise an arbitrary element is generated. elementsUnlessEmpty :: Arbitrary a => [a] -> Gen a -- | Generates two elements. two :: Gen a -> Gen (a, a) -- | Generates three elements. three :: Gen a -> Gen (a, a, a) -- | Runs the tests, and returns True if all tests were successful. runTests :: String -> [IO Bool] -> IO Bool module Agda.Utils.QuickCheck isSuccess :: Result -> Bool quickCheck' :: Testable prop => prop -> IO Bool quickCheckWith' :: Testable prop => Args -> prop -> IO Bool -- | Utilities for the Either type module Agda.Utils.Either -- | Loop while we have an exception. whileLeft :: Monad m => (a -> Either b c) -> (a -> b -> m a) -> (a -> c -> m d) -> a -> m d -- | Monadic version of either with a different argument ordering. caseEitherM :: Monad m => m (Either a b) -> (a -> m c) -> (b -> m c) -> m c -- | Either is a bifunctor. mapEither :: (a -> c) -> (b -> d) -> Either a b -> Either c d -- | 'Either _ b' is a functor. mapLeft :: (a -> c) -> Either a b -> Either c b -- | 'Either a' is a functor. mapRight :: (b -> d) -> Either a b -> Either a d -- | Either is bitraversable. traverseEither :: Functor f => (a -> f c) -> (b -> f d) -> Either a b -> f (Either c d) -- | Returns True iff the argument is Left x for -- some x. Note: from base >= 4.7.0.0 already -- present in Data.Either. isLeft :: Either a b -> Bool -- | Returns True iff the argument is Right x for -- some x. Note: from base >= 4.7.0.0 already -- present in Data.Either. isRight :: Either a b -> Bool -- | Analogue of fromMaybe. fromLeft :: (b -> a) -> Either a b -> a -- | Analogue of fromMaybe. fromRight :: (a -> b) -> Either a b -> b -- | Safe projection from Left. maybeLeft (Left a) = Just a -- maybeLeft Right{} = Nothing maybeLeft :: Either a b -> Maybe a -- | Safe projection from Right. maybeRight (Right b) = Just b -- maybeRight Left{} = Nothing maybeRight :: Either a b -> Maybe b -- | Returns Just with tags stripped if all elements -- are to the Left, and otherwise Nothing. allLeft :: [Either a b] -> Maybe [a] -- | Returns Just with tags stripped if all elements -- are to the right, and otherwise Nothing. -- --
--   allRight xs ==
--     if all isRight xs then
--       Just (map ((Right x) -> x) xs)
--      else
--       Nothing
--   
allRight :: [Either a b] -> Maybe [b] tests :: IO Bool -- | Semirings. module Agda.Termination.Semiring -- | HasZero is needed for sparse matrices, to tell which is the -- element that does not have to be stored. It is a cut-down version of -- SemiRing which is definable without the implicit -- ?cutoff. class Eq a => HasZero a zeroElement :: HasZero a => a -- | SemiRing type class. Additive monoid with multiplication operation. -- Inherit addition and zero from Monoid. class (Eq a, Monoid a) => SemiRing a multiply :: SemiRing a => a -> a -> a -- | Semirings. data Semiring a Semiring :: (a -> a -> a) -> (a -> a -> a) -> a -> Semiring a -- | Addition. [add] :: Semiring a -> a -> a -> a -- | Multiplication. [mul] :: Semiring a -> a -> a -> a -- | Zero. The one is never used in matrix multiplication , one :: a -- ^ -- One. [zero] :: Semiring a -> a -- | Semiring invariant. semiringInvariant :: (Arbitrary a, Eq a, Show a) => Semiring a -> a -> a -> a -> Bool integerSemiring :: Semiring Integer intSemiring :: Semiring Int -- | The standard semiring on Bools. boolSemiring :: Semiring Bool tests :: IO Bool instance Agda.Termination.Semiring.HasZero GHC.Integer.Type.Integer instance Agda.Termination.Semiring.HasZero GHC.Types.Int module Agda.Utils.PartialOrd -- | The result of comparing two things (of the same type). data PartialOrdering -- | Less than. POLT :: PartialOrdering -- | Less or equal than. POLE :: PartialOrdering -- | Equal POEQ :: PartialOrdering -- | Greater or equal. POGE :: PartialOrdering -- | Greater than. POGT :: PartialOrdering -- | No information (incomparable). POAny :: PartialOrdering -- | Comparing the information content of two elements of -- PartialOrdering. More precise information is smaller. -- -- Includes equality: x leqPO x == True. leqPO :: PartialOrdering -> PartialOrdering -> Bool -- | Opposites. -- -- related a po b iff related b (oppPO po) a. oppPO :: PartialOrdering -> PartialOrdering -- | Combining two pieces of information (picking the least information). -- Used for the dominance ordering on tuples. -- -- orPO is associative, commutative, and idempotent. -- orPO has dominant element POAny, but no neutral -- element. orPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -- | Chains (transitivity) x R y S z. -- -- seqPO is associative, commutative, and idempotent. -- seqPO has dominant element POAny and neutral element -- (unit) POEQ. seqPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -- | Partial ordering forms a monoid under sequencing. -- | Embed Ordering. fromOrdering :: Ordering -> PartialOrdering -- | Represent a non-empty disjunction of Orderings as -- PartialOrdering. fromOrderings :: [Ordering] -> PartialOrdering -- | A PartialOrdering information is a disjunction of -- Ordering informations. toOrderings :: PartialOrdering -> [Ordering] type Comparable a = a -> a -> PartialOrdering -- | Decidable partial orderings. class PartialOrd a comparable :: PartialOrd a => Comparable a -- | Any Ord is a PartialOrd. comparableOrd :: Ord a => Comparable a -- | Are two elements related in a specific way? -- -- related a o b holds iff comparable a b is contained -- in o. related :: PartialOrd a => a -> PartialOrdering -> a -> Bool -- | Nothing and Just _ are unrelated. -- -- Partial ordering for Maybe a is the same as for Either () -- a. -- | Partial ordering for disjoint sums: Left _ and Right -- _ are unrelated. -- | Pointwise partial ordering for tuples. -- -- related (x1,x2) o (y1,y2) iff related x1 o x2 and -- related y1 o y2. -- | Pointwise comparison wrapper. newtype Pointwise a Pointwise :: a -> Pointwise a [pointwise] :: Pointwise a -> a -- | The pointwise ordering for lists of the same length. -- -- There are other partial orderings for lists, e.g., prefix, sublist, -- subset, lexicographic, simultaneous order. -- | Inclusion comparison wrapper. newtype Inclusion a Inclusion :: a -> Inclusion a [inclusion] :: Inclusion a -> a -- | Sublist for ordered lists. -- | Sets are partially ordered by inclusion. -- | Less is ``less general'' (i.e., more precise). -- | We test our properties on integer sets ordered by inclusion. newtype ISet ISet :: Inclusion (Set Int) -> ISet [iset] :: ISet -> Inclusion (Set Int) -- | Any two elements are related in the way comparable -- computes. prop_comparable_related :: ISet -> ISet -> Bool -- |
--   flip comparable a b == oppPO (comparable a b)
--   
prop_oppPO :: ISet -> ISet -> Bool -- | Auxiliary function: lists to sets = sorted duplicate-free lists. sortUniq :: [Ordering] -> [Ordering] -- | leqPO is inclusion of the associated Ordering sets. prop_leqPO_sound :: PartialOrdering -> PartialOrdering -> Bool -- | orPO amounts to the union of the associated Ordering -- sets. Except that 'orPO POLT POGT == POAny' which should also include -- POEQ. prop_orPO_sound :: PartialOrdering -> PartialOrdering -> Bool -- | orPO is associative. prop_associative_orPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -> Bool -- | orPO is commutative. prop_commutative_orPO :: PartialOrdering -> PartialOrdering -> Bool -- | orPO is idempotent. prop_idempotent_orPO :: PartialOrdering -> Bool -- | The dominant element wrt. orPO is POAny. prop_zero_orPO :: PartialOrdering -> Bool -- | Soundness of seqPO. -- -- As QuickCheck test, this property is inefficient, see -- prop_seqPO. property_seqPO :: ISet -> PartialOrdering -> ISet -> PartialOrdering -> ISet -> Property -- | A more efficient way of stating soundness of seqPO. prop_seqPO :: ISet -> ISet -> ISet -> Bool -- | The unit of seqPO is POEQ. prop_identity_seqPO :: PartialOrdering -> Bool -- | The zero of seqPO is POAny. prop_zero_seqPO :: PartialOrdering -> Bool -- | seqPO is associative. prop_associative_seqPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -> Bool -- | seqPO is also commutative. prop_commutative_seqPO :: PartialOrdering -> PartialOrdering -> Bool -- | seqPO is idempotent. prop_idempotent_seqPO :: PartialOrdering -> Bool -- | seqPO distributes over orPO. prop_distributive_seqPO_orPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -> Bool -- | The result of toOrderings is a sorted list without duplicates. prop_sorted_toOrderings :: PartialOrdering -> Bool -- | From Ordering to PartialOrdering and back is the -- identity. prop_toOrderings_after_fromOrdering :: Ordering -> Bool -- | From PartialOrdering to Orderings and back is the -- identity. prop_fromOrderings_after_toOrderings :: PartialOrdering -> Bool -- | From Orderings to PartialOrdering and back is the -- identity. Except for [LT,GT] which is a non-canonical -- representative of POAny. prop_toOrderings_after_fromOrderings :: NonEmptyList Ordering -> Bool -- | Pairs are related iff both components are related. prop_related_pair :: ISet -> ISet -> ISet -> ISet -> PartialOrdering -> Bool -- | Comparing PartialOrderings amounts to compare their -- representation as Ordering sets. prop_comparable_PartialOrdering :: PartialOrdering -> PartialOrdering -> Bool -- | All tests as collected by quickCheckAll. -- -- Using quickCheckAll is convenient and superior to the manual -- enumeration of tests, since the name of the property is added -- automatically. tests :: IO Bool instance GHC.Show.Show Agda.Utils.PartialOrd.ISet instance Agda.Utils.PartialOrd.PartialOrd Agda.Utils.PartialOrd.ISet instance GHC.Classes.Ord Agda.Utils.PartialOrd.ISet instance GHC.Classes.Eq Agda.Utils.PartialOrd.ISet instance GHC.Base.Functor Agda.Utils.PartialOrd.Inclusion instance GHC.Show.Show a => GHC.Show.Show (Agda.Utils.PartialOrd.Inclusion a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Utils.PartialOrd.Inclusion a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Utils.PartialOrd.Inclusion a) instance GHC.Base.Functor Agda.Utils.PartialOrd.Pointwise instance GHC.Show.Show a => GHC.Show.Show (Agda.Utils.PartialOrd.Pointwise a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Utils.PartialOrd.Pointwise a) instance GHC.Enum.Bounded Agda.Utils.PartialOrd.PartialOrdering instance GHC.Enum.Enum Agda.Utils.PartialOrd.PartialOrdering instance GHC.Show.Show Agda.Utils.PartialOrd.PartialOrdering instance GHC.Classes.Eq Agda.Utils.PartialOrd.PartialOrdering instance GHC.Base.Monoid Agda.Utils.PartialOrd.PartialOrdering instance Agda.Utils.PartialOrd.PartialOrd GHC.Types.Int instance Agda.Utils.PartialOrd.PartialOrd GHC.Integer.Type.Integer instance Agda.Utils.PartialOrd.PartialOrd () instance Agda.Utils.PartialOrd.PartialOrd a => Agda.Utils.PartialOrd.PartialOrd (GHC.Base.Maybe a) instance (Agda.Utils.PartialOrd.PartialOrd a, Agda.Utils.PartialOrd.PartialOrd b) => Agda.Utils.PartialOrd.PartialOrd (Data.Either.Either a b) instance (Agda.Utils.PartialOrd.PartialOrd a, Agda.Utils.PartialOrd.PartialOrd b) => Agda.Utils.PartialOrd.PartialOrd (a, b) instance Agda.Utils.PartialOrd.PartialOrd a => Agda.Utils.PartialOrd.PartialOrd (Agda.Utils.PartialOrd.Pointwise [a]) instance GHC.Classes.Ord a => Agda.Utils.PartialOrd.PartialOrd (Agda.Utils.PartialOrd.Inclusion [a]) instance GHC.Classes.Ord a => Agda.Utils.PartialOrd.PartialOrd (Agda.Utils.PartialOrd.Inclusion (Data.Set.Base.Set a)) instance Agda.Utils.PartialOrd.PartialOrd Agda.Utils.PartialOrd.PartialOrdering instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Utils.PartialOrd.PartialOrdering instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Utils.PartialOrd.ISet -- | Constructing singleton collections. module Agda.Utils.Singleton class Singleton el coll | coll -> el singleton :: Singleton el coll => el -> coll instance Agda.Utils.Singleton.Singleton a (GHC.Base.Maybe a) instance Agda.Utils.Singleton.Singleton a [a] instance Agda.Utils.Singleton.Singleton a (Data.Sequence.Seq a) instance Agda.Utils.Singleton.Singleton a (Data.Set.Base.Set a) instance Agda.Utils.Singleton.Singleton GHC.Types.Int Data.IntSet.Base.IntSet instance Agda.Utils.Singleton.Singleton (k, a) (Data.Map.Base.Map k a) instance Agda.Utils.Singleton.Singleton (GHC.Types.Int, a) (Data.IntMap.Base.IntMap a) instance Data.Hashable.Class.Hashable a => Agda.Utils.Singleton.Singleton a (Data.HashSet.HashSet a) instance Data.Hashable.Class.Hashable k => Agda.Utils.Singleton.Singleton (k, a) (Data.HashMap.Base.HashMap k a) module Agda.Utils.ReadP data ReadP t a -- | Consumes and returns the next character. Fails if there is no input -- left. get :: ReadP t t -- | Look-ahead: returns the part of the input that is left, without -- consuming it. look :: ReadP t [t] -- | Symmetric choice. (+++) :: ReadP t a -> ReadP t a -> ReadP t a -- | Local, exclusive, left-biased choice: If left parser locally produces -- any result at all, then right parser is not used. (<++) :: ReadP t a -> ReadP t a -> ReadP t a -- | Transforms a parser into one that does the same, but in addition -- returns the exact characters read. IMPORTANT NOTE: gather gives -- a runtime error if its first argument is built using any occurrences -- of readS_to_P. gather :: ReadP t a -> ReadP t ([t], a) -- | Run a parser on a list of tokens. Returns the list of complete -- matches. parse :: ReadP t a -> [t] -> [a] parse' :: ReadP t a -> [t] -> Either a [t] -- | Always fails. pfail :: ReadP t a -- | Consumes and returns the next character, if it satisfies the specified -- predicate. satisfy :: (t -> Bool) -> ReadP t t -- | Parses and returns the specified character. char :: Eq t => t -> ReadP t t -- | Parses and returns the specified string. string :: Eq t => [t] -> ReadP t [t] -- | Parses the first zero or more characters satisfying the predicate. munch :: (t -> Bool) -> ReadP t [t] -- | Parses the first one or more characters satisfying the predicate. munch1 :: (t -> Bool) -> ReadP t [t] -- | Skips all whitespace. skipSpaces :: ReadP Char () -- | Combines all parsers in the specified list. choice :: [ReadP t a] -> ReadP t a -- | count n p parses n occurrences of p in -- sequence. A list of results is returned. count :: Int -> ReadP t a -> ReadP t [a] -- | between open close p parses open, followed by -- p and finally close. Only the value of p is -- returned. between :: ReadP t open -> ReadP t close -> ReadP t a -> ReadP t a -- | option x p will either parse p or return x -- without consuming any input. option :: a -> ReadP t a -> ReadP t a -- | optional p optionally parses p and always returns -- (). optional :: ReadP t a -> ReadP t () -- | Parses zero or more occurrences of the given parser. many :: ReadP t a -> ReadP t [a] -- | Parses one or more occurrences of the given parser. many1 :: ReadP t a -> ReadP t [a] -- | Like many, but discards the result. skipMany :: ReadP t a -> ReadP t () -- | Like many1, but discards the result. skipMany1 :: ReadP t a -> ReadP t () -- | sepBy p sep parses zero or more occurrences of p, -- separated by sep. Returns a list of values returned by -- p. sepBy :: ReadP t a -> ReadP t sep -> ReadP t [a] -- | sepBy1 p sep parses one or more occurrences of p, -- separated by sep. Returns a list of values returned by -- p. sepBy1 :: ReadP t a -> ReadP t sep -> ReadP t [a] -- | endBy p sep parses zero or more occurrences of p, -- separated and ended by sep. endBy :: ReadP t a -> ReadP t sep -> ReadP t [a] -- | endBy p sep parses one or more occurrences of p, -- separated and ended by sep. endBy1 :: ReadP t a -> ReadP t sep -> ReadP t [a] -- | chainr p op x parses zero or more occurrences of p, -- separated by op. Returns a value produced by a right -- associative application of all functions returned by op. If -- there are no occurrences of p, x is returned. chainr :: ReadP t a -> ReadP t (a -> a -> a) -> a -> ReadP t a -- | chainl p op x parses zero or more occurrences of p, -- separated by op. Returns a value produced by a left -- associative application of all functions returned by op. If -- there are no occurrences of p, x is returned. chainl :: ReadP t a -> ReadP t (a -> a -> a) -> a -> ReadP t a -- | Like chainl, but parses one or more occurrences of p. chainl1 :: ReadP t a -> ReadP t (a -> a -> a) -> ReadP t a -- | Like chainr, but parses one or more occurrences of p. chainr1 :: ReadP t a -> ReadP t (a -> a -> a) -> ReadP t a -- | manyTill p end parses zero or more occurrences of p, -- until end succeeds. Returns a list of values returned by -- p. manyTill :: ReadP t a -> ReadP t end -> ReadP t [a] instance GHC.Base.Functor (Agda.Utils.ReadP.P t) instance GHC.Base.Applicative (Agda.Utils.ReadP.P t) instance GHC.Base.Monad (Agda.Utils.ReadP.P t) instance GHC.Base.Alternative (Agda.Utils.ReadP.P t) instance GHC.Base.MonadPlus (Agda.Utils.ReadP.P t) instance GHC.Base.Functor (Agda.Utils.ReadP.ReadP t) instance GHC.Base.Applicative (Agda.Utils.ReadP.ReadP t) instance GHC.Base.Monad (Agda.Utils.ReadP.ReadP t) instance GHC.Base.Alternative (Agda.Utils.ReadP.ReadP t) instance GHC.Base.MonadPlus (Agda.Utils.ReadP.ReadP t) -- | Text IO using the UTF8 character encoding. module Agda.Utils.IO.UTF8 -- | Reads a UTF8-encoded text file and converts all Unicode line endings -- into '\n'. readTextFile :: FilePath -> IO String -- | Writes UTF8-encoded text to the handle, which should be opened for -- writing and in text mode. The native convention for line endings is -- used. -- -- The handle's text encoding is not necessarily preserved, it is changed -- to UTF8. hPutStr :: Handle -> String -> IO () -- | Writes a UTF8-encoded text file. The native convention for line -- endings is used. writeFile :: FilePath -> String -> IO () module Agda.Utils.Function -- | Repeat a state transition f :: a -> (b, a) with output -- b while condition cond on the output is true. Return -- all intermediate results and the final result where cond is -- False. -- -- Postconditions (when it terminates): fst (last (iterWhile cond f -- a)) == False. all fst (init (interWhile cond f a)). iterWhile :: (b -> Bool) -> (a -> (b, a)) -> a -> [(b, a)] -- | Repeat something while a condition on some state is true. Return the -- last state (including the changes of the last transition, even if the -- condition became false then). repeatWhile :: (a -> (Bool, a)) -> a -> a -- | Monadic version of repeatWhile. repeatWhileM :: (Monad m) => (a -> m (Bool, a)) -> a -> m a -- | A version of the trampoline function. -- -- The usual function iterates f :: a -> Maybe a as long as -- Just{} is returned, and returns the last value of a -- upon Nothing. -- -- usualTrampoline f = trampolineWhile $ a -> maybe (False,a) -- (True,) (f a). -- -- trampolineWhile is very similar to repeatWhile, only -- that it discards the state on which the condition went False, -- and returns the last state on which the condition was True. trampolineWhile :: (a -> (Bool, a)) -> a -> a -- | Monadic version of trampolineWhile. trampolineWhileM :: (Monad m) => (a -> m (Bool, a)) -> a -> m a -- | More general trampoline, which allows some final computation from -- iteration state a into result type b. trampoline :: (a -> Either b a) -> a -> b -- | Monadic version of trampoline. trampolineM :: Monad m => (a -> m (Either b a)) -> a -> m b -- | Iteration to fixed-point. -- -- iterateUntil r f a0 iterates endofunction f, -- starting with a0, until r relates its result to its -- input, i.e., f a r a. -- -- This is the generic pattern behind saturation algorithms. -- -- If f is monotone with regard to r, meaning a -- r b implies f a r f b, and -- f-chains starting with a0 are finite then iteration -- is guaranteed to terminate. -- -- A typical instance will work on sets, and r could be set -- inclusion, and a0 the empty set, and f the step -- function of a saturation algorithm. iterateUntil :: (a -> a -> Bool) -> (a -> a) -> a -> a -- | Monadic version of iterateUntil. iterateUntilM :: Monad m => (a -> a -> Bool) -> (a -> m a) -> a -> m a -- | iterate' n f x applies f to x -- n times and returns the result. -- -- The applications are calculated strictly. iterate' :: Integral i => i -> (a -> a) -> a -> a -- | applyWhen b f a applies f to a when -- b. applyWhen :: Bool -> (a -> a) -> a -> a -- | applyUnless b f a applies f to a unless -- b. applyUnless :: Bool -> (a -> a) -> a -> a -- | Monadic version of applyWhen applyWhenM :: (Monad m) => m Bool -> (m a -> m a) -> m a -> m a -- | Monadic version of applyUnless applyUnlessM :: (Monad m) => m Bool -> (m a -> m a) -> m a -> m a module Agda.TypeChecking.SizedTypes.Utils debug :: Bool trace :: String -> a -> a traceM :: Applicative f => String -> f () class Eq a => Top a where isTop = (== top) top :: Top a => a isTop :: Top a => a -> Bool class Plus a b c plus :: Plus a b c => a -> b -> c class MeetSemiLattice a meet :: MeetSemiLattice a => a -> a -> a -- | Semiring with idempotent + == dioid class (MeetSemiLattice a, Top a) => Dioid a compose :: Dioid a => a -> a -> a unitCompose :: Dioid a => a instance Agda.TypeChecking.SizedTypes.Utils.Plus GHC.Types.Int GHC.Types.Int GHC.Types.Int -- | Syntax of size expressions and constraints. module Agda.TypeChecking.SizedTypes.Syntax -- | Constant finite sizes n >= 0. newtype Offset O :: Int -> Offset -- | Fixed size variables i. newtype Rigid RigidId :: String -> Rigid [rigidId] :: Rigid -> String -- | Size meta variables X to solve for. newtype Flex FlexId :: String -> Flex [flexId] :: Flex -> String -- | Size expressions appearing in constraints. data SizeExpr' rigid flex -- | Constant number n. Const :: Offset -> SizeExpr' rigid flex [offset] :: SizeExpr' rigid flex -> Offset -- | Variable plus offset i + n. Rigid :: rigid -> Offset -> SizeExpr' rigid flex [rigid] :: SizeExpr' rigid flex -> rigid [offset] :: SizeExpr' rigid flex -> Offset -- | Infinity . Infty :: SizeExpr' rigid flex -- | Meta variable X + n. Flex :: flex -> Offset -> SizeExpr' rigid flex [flex] :: SizeExpr' rigid flex -> flex [offset] :: SizeExpr' rigid flex -> Offset type SizeExpr = SizeExpr' Rigid Flex -- | Comparison operator, e.g. for size expression. data Cmp -- | <. Lt :: Cmp -- | . Le :: Cmp -- | Comparison operator is ordered Lt < Le. -- | Constraint: an inequation between size expressions, e.g. X < -- ∞ or i + 3 ≤ j. data Constraint' rigid flex Constraint :: SizeExpr' rigid flex -> Cmp -> SizeExpr' rigid flex -> Constraint' rigid flex [leftExpr] :: Constraint' rigid flex -> SizeExpr' rigid flex [cmp] :: Constraint' rigid flex -> Cmp [rightExpr] :: Constraint' rigid flex -> SizeExpr' rigid flex type Constraint = Constraint' Rigid Flex -- | What type of solution are we looking for? data Polarity Least :: Polarity Greatest :: Polarity -- | Assigning a polarity to a flexible variable. data PolarityAssignment flex PolarityAssignment :: Polarity -> flex -> PolarityAssignment flex -- | Type of solution wanted for each flexible. type Polarities flex = Map flex Polarity emptyPolarities :: Polarities flex polaritiesFromAssignments :: Ord flex => [PolarityAssignment flex] -> Polarities flex -- | Default polarity is Least. getPolarity :: Ord flex => Polarities flex -> flex -> Polarity -- | Partial substitution from flexible variables to size expression. type Solution rigid flex = Map flex (SizeExpr' rigid flex) -- | Executing a substitution. class Substitute r f a subst :: Substitute r f a => Solution r f -> a -> a -- | Add offset to size expression. type CTrans r f = Constraint' r f -> Maybe [Constraint' r f] -- | Returns Nothing if we have a contradictory constraint. simplify1 :: Eq r => CTrans r f -> CTrans r f -- | Le acts as True, Lt as False. ifLe :: Cmp -> a -> a -> a -- | Interpret Cmp as relation on Offset. compareOffset :: Offset -> Cmp -> Offset -> Bool -- | Offsets + n must be non-negative class ValidOffset a validOffset :: ValidOffset a => a -> Bool -- | Make offsets non-negative by rounding up. class TruncateOffset a truncateOffset :: TruncateOffset a => a -> a -- | The rigid variables contained in a pice of syntax. class Rigids r a rigids :: Rigids r a => a -> Set r -- | The flexibe variables contained in a pice of syntax. class Flexs flex a | a -> flex flexs :: Flexs flex a => a -> Set flex instance GHC.Classes.Ord Agda.TypeChecking.SizedTypes.Syntax.Polarity instance GHC.Classes.Eq Agda.TypeChecking.SizedTypes.Syntax.Polarity instance Data.Traversable.Traversable (Agda.TypeChecking.SizedTypes.Syntax.Constraint' rigid) instance Data.Foldable.Foldable (Agda.TypeChecking.SizedTypes.Syntax.Constraint' rigid) instance GHC.Base.Functor (Agda.TypeChecking.SizedTypes.Syntax.Constraint' rigid) instance GHC.Enum.Enum Agda.TypeChecking.SizedTypes.Syntax.Cmp instance GHC.Enum.Bounded Agda.TypeChecking.SizedTypes.Syntax.Cmp instance GHC.Classes.Eq Agda.TypeChecking.SizedTypes.Syntax.Cmp instance Data.Traversable.Traversable (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' rigid) instance Data.Foldable.Foldable (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' rigid) instance GHC.Base.Functor (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' rigid) instance (GHC.Classes.Ord rigid, GHC.Classes.Ord flex) => GHC.Classes.Ord (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' rigid flex) instance (GHC.Classes.Eq rigid, GHC.Classes.Eq flex) => GHC.Classes.Eq (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' rigid flex) instance GHC.Classes.Ord Agda.TypeChecking.SizedTypes.Syntax.Flex instance GHC.Classes.Eq Agda.TypeChecking.SizedTypes.Syntax.Flex instance GHC.Classes.Ord Agda.TypeChecking.SizedTypes.Syntax.Rigid instance GHC.Classes.Eq Agda.TypeChecking.SizedTypes.Syntax.Rigid instance GHC.Enum.Enum Agda.TypeChecking.SizedTypes.Syntax.Offset instance GHC.Show.Show Agda.TypeChecking.SizedTypes.Syntax.Offset instance GHC.Num.Num Agda.TypeChecking.SizedTypes.Syntax.Offset instance GHC.Classes.Ord Agda.TypeChecking.SizedTypes.Syntax.Offset instance GHC.Classes.Eq Agda.TypeChecking.SizedTypes.Syntax.Offset instance Agda.TypeChecking.SizedTypes.Utils.MeetSemiLattice Agda.TypeChecking.SizedTypes.Syntax.Offset instance Agda.TypeChecking.SizedTypes.Utils.Plus Agda.TypeChecking.SizedTypes.Syntax.Offset Agda.TypeChecking.SizedTypes.Syntax.Offset Agda.TypeChecking.SizedTypes.Syntax.Offset instance Test.QuickCheck.Arbitrary.Arbitrary Agda.TypeChecking.SizedTypes.Syntax.Offset instance GHC.Show.Show Agda.TypeChecking.SizedTypes.Syntax.Rigid instance GHC.Show.Show Agda.TypeChecking.SizedTypes.Syntax.Flex instance Agda.TypeChecking.SizedTypes.Utils.Dioid Agda.TypeChecking.SizedTypes.Syntax.Cmp instance GHC.Classes.Ord Agda.TypeChecking.SizedTypes.Syntax.Cmp instance Agda.TypeChecking.SizedTypes.Utils.MeetSemiLattice Agda.TypeChecking.SizedTypes.Syntax.Cmp instance Agda.TypeChecking.SizedTypes.Utils.Top Agda.TypeChecking.SizedTypes.Syntax.Cmp instance Test.QuickCheck.Arbitrary.Arbitrary Agda.TypeChecking.SizedTypes.Syntax.Cmp instance GHC.Classes.Ord f => Agda.TypeChecking.SizedTypes.Syntax.Substitute r f (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' r f) instance GHC.Classes.Ord f => Agda.TypeChecking.SizedTypes.Syntax.Substitute r f (Agda.TypeChecking.SizedTypes.Syntax.Constraint' r f) instance Agda.TypeChecking.SizedTypes.Syntax.Substitute r f a => Agda.TypeChecking.SizedTypes.Syntax.Substitute r f [a] instance Agda.TypeChecking.SizedTypes.Utils.Plus (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' r f) Agda.TypeChecking.SizedTypes.Syntax.Offset (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' r f) instance (GHC.Show.Show r, GHC.Show.Show f) => GHC.Show.Show (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' r f) instance GHC.Show.Show Agda.TypeChecking.SizedTypes.Syntax.Polarity instance GHC.Show.Show flex => GHC.Show.Show (Agda.TypeChecking.SizedTypes.Syntax.PolarityAssignment flex) instance GHC.Show.Show Agda.TypeChecking.SizedTypes.Syntax.Cmp instance (GHC.Show.Show r, GHC.Show.Show f) => GHC.Show.Show (Agda.TypeChecking.SizedTypes.Syntax.Constraint' r f) instance Agda.TypeChecking.SizedTypes.Syntax.ValidOffset Agda.TypeChecking.SizedTypes.Syntax.Offset instance Agda.TypeChecking.SizedTypes.Syntax.ValidOffset (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' r f) instance Agda.TypeChecking.SizedTypes.Syntax.TruncateOffset Agda.TypeChecking.SizedTypes.Syntax.Offset instance Agda.TypeChecking.SizedTypes.Syntax.TruncateOffset (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' r f) instance (GHC.Classes.Ord r, Agda.TypeChecking.SizedTypes.Syntax.Rigids r a) => Agda.TypeChecking.SizedTypes.Syntax.Rigids r [a] instance Agda.TypeChecking.SizedTypes.Syntax.Rigids r (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' r f) instance GHC.Classes.Ord r => Agda.TypeChecking.SizedTypes.Syntax.Rigids r (Agda.TypeChecking.SizedTypes.Syntax.Constraint' r f) instance (GHC.Classes.Ord flex, Agda.TypeChecking.SizedTypes.Syntax.Flexs flex a) => Agda.TypeChecking.SizedTypes.Syntax.Flexs flex [a] instance GHC.Classes.Ord flex => Agda.TypeChecking.SizedTypes.Syntax.Flexs flex (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' rigid flex) instance GHC.Classes.Ord flex => Agda.TypeChecking.SizedTypes.Syntax.Flexs flex (Agda.TypeChecking.SizedTypes.Syntax.Constraint' rigid flex) module Agda.Version -- | The version of Agda. version :: String module Agda.Utils.Tuple -- | Bifunctoriality for pairs. (-*-) :: (a -> c) -> (b -> d) -> (a, b) -> (c, d) -- |
--   mapFst f = f -*- id
--   
mapFst :: (a -> c) -> (a, b) -> (c, b) -- |
--   mapSnd g = id -*- g
--   
mapSnd :: (b -> d) -> (a, b) -> (a, d) -- | Lifted pairing. (/\) :: (a -> b) -> (a -> c) -> a -> (b, c) -- | Swap. (Only in Data.Tuple from base-4.3) swap :: (a, b) -> (b, a) fst3 :: (a, b, c) -> a snd3 :: (a, b, c) -> b thd3 :: (a, b, c) -> c uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e -- | Monadic version of -*-. mapPairM :: (Applicative m) => (a -> m c) -> (b -> m d) -> (a, b) -> m (c, d) -- | Monadic mapFst. mapFstM :: (Applicative m) => (a -> m c) -> (a, b) -> m (c, b) -- | Monadic mapSnd. mapSndM :: (Applicative m) => (b -> m d) -> (a, b) -> m (a, d) newtype List2 a List2 :: (a, a) -> List2 a [list2] :: List2 a -> (a, a) instance Data.Traversable.Traversable Agda.Utils.Tuple.List2 instance Data.Foldable.Foldable Agda.Utils.Tuple.List2 instance GHC.Base.Functor Agda.Utils.Tuple.List2 instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Utils.Tuple.List2 a) instance GHC.Base.Applicative Agda.Utils.Tuple.List2 module Agda.Utils.Update -- | The Change monad. data Change a -- | The class of change monads. class Monad m => MonadChange m tellDirty :: MonadChange m => m () listenDirty :: MonadChange m => m a -> m (a, Bool) -- | Run a Change computation, returning result plus change flag. runChange :: Change a -> (a, Bool) type Updater a = a -> Change a -- | Replace result of updating with original input if nothing has changed. sharing :: Updater a -> Updater a -- | Blindly run an updater. runUpdater :: Updater a -> a -> (a, Bool) -- | Mark a computation as dirty. dirty :: Updater a ifDirty :: MonadChange m => m a -> (a -> m b) -> (a -> m b) -> m b -- | Like Functor, but preserving sharing. class Traversable f => Updater1 f where updater1 = traverse updates1 f = sharing $ updater1 f update1 f = evalUpdater $ updater1 f updater1 :: Updater1 f => Updater a -> Updater (f a) updates1 :: Updater1 f => Updater a -> Updater (f a) update1 :: Updater1 f => Updater a -> EndoFun (f a) -- | Like Bifunctor, but preserving sharing. class Updater2 f where updates2 f1 f2 = sharing $ updater2 f1 f2 update2 f1 f2 = evalUpdater $ updater2 f1 f2 updater2 :: Updater2 f => Updater a -> Updater b -> Updater (f a b) updates2 :: Updater2 f => Updater a -> Updater b -> Updater (f a b) update2 :: Updater2 f => Updater a -> Updater b -> EndoFun (f a b) instance GHC.Base.Monad Agda.Utils.Update.Change instance GHC.Base.Applicative Agda.Utils.Update.Change instance GHC.Base.Functor Agda.Utils.Update.Change instance Control.Monad.Trans.Class.MonadTrans Agda.Utils.Update.ChangeT instance GHC.Base.Monad m => GHC.Base.Monad (Agda.Utils.Update.ChangeT m) instance GHC.Base.Applicative m => GHC.Base.Applicative (Agda.Utils.Update.ChangeT m) instance GHC.Base.Functor m => GHC.Base.Functor (Agda.Utils.Update.ChangeT m) instance GHC.Base.Monad m => Agda.Utils.Update.MonadChange (Agda.Utils.Update.ChangeT m) instance Agda.Utils.Update.MonadChange Data.Functor.Identity.Identity instance Agda.Utils.Update.MonadChange Agda.Utils.Update.Change instance Agda.Utils.Update.Updater1 GHC.Base.Maybe instance Agda.Utils.Update.Updater1 [] instance Agda.Utils.Update.Updater2 (,) instance Agda.Utils.Update.Updater2 Data.Either.Either -- | An interface for reporting "impossible" errors module Agda.Utils.Impossible -- | "Impossible" errors, annotated with a file name and a line number -- corresponding to the source code location of the error. data Impossible Impossible :: String -> Integer -> Impossible -- | Abort by throwing an "impossible" error. You should not use this -- function directly. Instead use the macro in undefined.h. throwImpossible :: Impossible -> a -- | Catch an "impossible" error, if possible. catchImpossible :: IO a -> (Impossible -> IO a) -> IO a instance GHC.Show.Show Agda.Utils.Impossible.Impossible instance GHC.Exception.Exception Agda.Utils.Impossible.Impossible -- | Extend Maybe by common operations for the Maybe type. -- -- Note: since this module is usually imported unqualified, we do not use -- short names, but all names contain Maybe, Just, or -- 'Nothing. module Agda.Utils.Maybe -- | unionWith for collections of size <= 1. unionMaybeWith :: (a -> a -> a) -> Maybe a -> Maybe a -> Maybe a -- | Unzipping a list of length <= 1. unzipMaybe :: Maybe (a, b) -> (Maybe a, Maybe b) -- | Filtering a singleton list. -- --
--   filterMaybe p a = listToMaybe (filter p [a])
--   
filterMaybe :: (a -> Bool) -> a -> Maybe a -- | Version of mapMaybe with different argument ordering. forMaybe :: [a] -> (a -> Maybe b) -> [b] -- | Version of maybe with different argument ordering. Often, we -- want to case on a Maybe, do something interesting in the -- Just case, but only a default action in the Nothing -- case. Then, the argument ordering of caseMaybe is preferable. -- --
--   caseMaybe m d f = flip (maybe d) m f
--   
caseMaybe :: Maybe a -> b -> (a -> b) -> b -- | Monadic version of maybe. maybeM :: Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b -- | Monadic version of fromMaybe. fromMaybeM :: Monad m => m a -> m (Maybe a) -> m a -- | Monadic version of caseMaybe. That is, maybeM with a -- different argument ordering. caseMaybeM :: Monad m => m (Maybe a) -> m b -> (a -> m b) -> m b -- | caseMaybeM with flipped branches. ifJustM :: Monad m => m (Maybe a) -> (a -> m b) -> m b -> m b -- | A more telling name for forM_ for the Maybe collection -- type. Or: caseMaybe without the Nothing case. whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () -- | caseMaybe without the Just case. whenNothing :: Monad m => Maybe a -> m () -> m () -- | caseMaybeM without the Nothing case. whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m () -- | caseMaybeM without the Just case. whenNothingM :: Monad m => m (Maybe a) -> m () -> m () -- | Lazy version of allJust . sequence. (allJust = -- mapM for the Maybe monad.) Only executes monadic effect -- while isJust. allJustM :: Monad m => [m (Maybe a)] -> m (Maybe [a]) -- | Precondition: list not empty. allJustsOrNothings [Nothing, -- Nothing] = Just Nothing allJustsOrNothings [Just 0, Just 1] = Just $ -- Just [0,1] allJustsOrNothings [Just 0, Nothing] = Nothing allJustsOrNothings :: [Maybe a] -> Maybe (Maybe [a]) module Agda.ImpossibleTest impossibleTest :: a module Agda.Utils.Suffix -- | Is the character one of the subscripts '₀'-'₉'? isSubscriptDigit :: Char -> Bool -- | Converts '0'-'9' to '₀'-'₉'. -- -- Precondition: The digit needs to be in range. toSubscriptDigit :: Char -> Char -- | Converts '₀'-'₉' to '0'-'9'. -- -- Precondition: The digit needs to be in range. fromSubscriptDigit :: Char -> Char -- | Classification of identifier variants. data Suffix NoSuffix :: Suffix -- | Identifier ends in Int many primes. Prime :: Int -> Suffix -- | Identifier ends in number Int (ordinary digits). Index :: Int -> Suffix -- | Identifier ends in number Int (subscript digits). Subscript :: Int -> Suffix -- | Increase the suffix by one. If no suffix yet, put a subscript -- 1. nextSuffix :: Suffix -> Suffix -- | Parse suffix. suffixView :: String -> (String, Suffix) -- | Print suffix. addSuffix :: String -> Suffix -> String -- | Add first available Suffix to a name. nameVariant :: (String -> Bool) -> String -> String -- | An empty type with some useful instances. module Agda.Utils.Empty data Empty absurd :: Empty -> a instance GHC.Classes.Eq Agda.Utils.Empty.Empty instance GHC.Classes.Ord Agda.Utils.Empty.Empty instance GHC.Show.Show Agda.Utils.Empty.Empty -- | Additional functions for association lists. module Agda.Utils.AssocList -- | A finite map, represented as a set of pairs. -- -- Invariant: at most one value per key. type AssocList k v = [(k, v)] -- | O(n). Reexport lookup. lookup :: Eq k => k -> AssocList k v -> Maybe v -- | O(n). Get the domain (list of keys) of the finite map. keys :: AssocList k v -> [k] -- | O(1). Add a new binding. Assumes the binding is not yet in the list. insert :: k -> v -> AssocList k v -> AssocList k v -- | O(n). Update the value at a key. The key must be in the domain of the -- finite map. Otherwise, an internal error is raised. update :: Eq k => k -> v -> AssocList k v -> AssocList k v -- | O(n). Update the value at a key with a certain function. The key must -- be in the domain of the finite map. Otherwise, an internal error is -- raised. updateAt :: Eq k => k -> (v -> v) -> AssocList k v -> AssocList k v -- | O(n). Map over an association list, preserving the order. mapWithKey :: (k -> v -> v) -> AssocList k v -> AssocList k v -- | O(n). If called with a effect-producing function, violation of the -- invariant could matter here (duplicating effects). mapWithKeyM :: (Functor m, Applicative m) => (k -> v -> m v) -> AssocList k v -> m (AssocList k v) -- | O(n). Named in analogy to mapKeysMonotonic. To preserve the -- invariant, it is sufficient that the key transformation is injective -- (rather than monotonic). mapKeysMonotonic :: (k -> k') -> AssocList k v -> AssocList k' v module Agda.Utils.Map data EitherOrBoth a b L :: a -> EitherOrBoth a b B :: a -> b -> EitherOrBoth a b R :: b -> EitherOrBoth a b -- | Not very efficient (goes via a list), but it'll do. unionWithM :: (Ord k, Functor m, Monad m) => (a -> a -> m a) -> Map k a -> Map k a -> m (Map k a) insertWithKeyM :: (Ord k, Monad m) => (k -> a -> a -> m a) -> k -> a -> Map k a -> m (Map k a) -- | Big conjunction over a map. allWithKey :: (k -> a -> Bool) -> Map k a -> Bool -- | Filter a map based on the keys. filterKeys :: Ord k => (k -> Bool) -> Map k a -> Map k a -- | Unzip a map. unzip :: Map k (a, b) -> (Map k a, Map k b) unzip3 :: Map k (a, b, c) -> (Map k a, Map k b, Map k c) -- | Utilities for functors. module Agda.Utils.Functor ($>) :: Functor f => f a -> b -> f b -- | Composition: pure function after functorial (monadic) function. (<.>) :: Functor m => (b -> c) -> (a -> m b) -> a -> m c -- | The true pure for loop. for is a misnomer, it should -- be forA. for :: Functor m => m a -> (a -> b) -> m b -- | Infix version of for. (<&>) :: Functor m => m a -> (a -> b) -> m b -- | A decoration is a functor that is traversable into any functor. -- -- The Functor superclass is given because of the limitations of -- the Haskell class system. traverseF actually implies -- functoriality. -- -- Minimal complete definition: traverseF or -- distributeF. class Functor t => Decoration t where traverseF f = distributeF . fmap f distributeF = traverseF id -- | traverseF is the defining property. traverseF :: (Decoration t, Functor m) => (a -> m b) -> t a -> m (t b) -- | Decorations commute into any functor. distributeF :: (Decoration t, Functor m) => t (m a) -> m (t a) -- | Any decoration is traversable with traverse = traverseF. Just -- like any Traversable is a functor, so is any decoration, given -- by just traverseF, a functor. dmap :: Decoration t => (a -> b) -> t a -> t b -- | Any decoration is a lens. set is a special case of -- dmap. dget :: Decoration t => t a -> a -- | The identity functor is a decoration. -- | Decorations compose. (Thus, they form a category.) -- | A typical decoration is pairing with some stuff. -- | An infix synonym for fmap. -- --

Examples

-- -- Convert from a Maybe Int to a -- Maybe String using show: -- --
--   >>> show <$> Nothing
--   Nothing
--   
--   >>> show <$> Just 3
--   Just "3"
--   
-- -- Convert from an Either Int Int to -- an Either Int String using -- show: -- --
--   >>> show <$> Left 17
--   Left 17
--   
--   >>> show <$> Right 17
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> (*2) <$> [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> even <$> (2,2)
--   (2,True)
--   
(<$>) :: Functor f => (a -> b) -> f a -> f b instance Agda.Utils.Functor.Decoration Data.Functor.Identity.Identity instance (Agda.Utils.Functor.Decoration d, Agda.Utils.Functor.Decoration t) => Agda.Utils.Functor.Decoration (Data.Functor.Compose.Compose d t) instance Agda.Utils.Functor.Decoration ((,) a) -- | A cut-down implementation of lenses, with names taken from Edward -- Kmett's lens package. module Agda.Utils.Lens -- | Van Laarhoven style homogeneous lenses. Mnemoic: "Lens inner outer". type Lens' i o = forall f. Functor f => (i -> f i) -> o -> f o -- | Get inner part i of structure o as designated by -- Lens' i o. (^.) :: o -> Lens' i o -> i -- | Set inner part i of structure o as designated by -- Lens' i o. set :: Lens' i o -> i -> o -> o -- | Modify inner part i of structure o using a function -- i -> i. over :: Lens' i o -> (i -> i) -> o -> o -- | Read a part of the state. use :: MonadState o m => Lens' i o -> m i -- | Write a part of the state. (.=) :: MonadState o m => Lens' i o -> i -> m () -- | Modify a part of the state. (%=) :: MonadState o m => Lens' i o -> (i -> i) -> m () -- | Modify a part of the state monadically. (%==) :: (MonadState o m, Functor m) => Lens' i o -> (i -> m i) -> m () -- | Modify a part of the state monadically, and return some result. (%%=) :: (MonadState o m, Functor m) => Lens' i o -> (i -> m (i, r)) -> m r -- | Ask for part of read-only state. view :: MonadReader o m => Lens' i o -> m i -- | Modify a part of the state in a subcomputation. locally :: MonadReader o m => Lens' i o -> (i -> i) -> m a -> m a -- | Infix version of for. (<&>) :: Functor m => m a -> (a -> b) -> m b -- | A simple overlay over Data.Map to manage unordered sets with -- duplicates. module Agda.Utils.Bag -- | A set with duplicates. Faithfully stores elements which are equal with -- regard to (==). newtype Bag a Bag :: Map a [a] -> Bag a [bag] :: Bag a -> Map a [a] null :: Bag a -> Bool size :: Bag a -> Int -- | bag ! a finds all elements equal to a. (!) :: Ord a => Bag a -> a -> [a] member :: Ord a => a -> Bag a -> Bool notMember :: Ord a => a -> Bag a -> Bool -- | Return the multiplicity of the given element. count :: Ord a => a -> Bag a -> Int empty :: Bag a singleton :: a -> Bag a union :: Ord a => Bag a -> Bag a -> Bag a unions :: Ord a => [Bag a] -> Bag a -- |
--   insert a b = union b (singleton a)
--   
insert :: Ord a => a -> Bag a -> Bag a -- |
--   fromList = unions . map singleton
--   
fromList :: Ord a => [a] -> Bag a -- | Returns the elements of the bag, grouped by equality (==). groups :: Bag a -> [[a]] -- | Returns the bag, with duplicates. toList :: Bag a -> [a] -- | Returns the bag without duplicates. keys :: Bag a -> [a] -- | Returns the bag, with duplicates. elems :: Bag a -> [a] toAscList :: Bag a -> [a] map :: (Ord a, Ord b) => (a -> b) -> Bag a -> Bag b traverse' :: (Applicative m, Ord b) => (a -> m b) -> Bag a -> m (Bag b) prop_count_empty :: Ord a => a -> Bool prop_count_singleton :: Ord a => a -> Bool prop_count_insert :: Ord a => a -> Bag a -> Bool prop_size_union :: Ord a => Bag a -> Bag a -> Bool prop_size_fromList :: Ord a => [a] -> Bool prop_fromList_toList :: Ord a => Bag a -> Bool prop_toList_fromList :: Ord a => [a] -> Bool prop_keys_fromList :: Ord a => [a] -> Bool prop_nonempty_groups :: Bag a -> Bool prop_map_id :: Ord a => Bag a -> Bool prop_map_compose :: (Ord a, Ord b, Ord c) => (b -> c) -> (a -> b) -> Bag a -> Bool prop_traverse_id :: Ord a => Bag a -> Bool -- | All tests as collected by quickCheckAll. -- -- Using quickCheckAll is convenient and superior to the manual -- enumeration of tests, since the name of the property is added -- automatically. tests :: IO Bool instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Utils.Bag.Bag a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Utils.Bag.Bag a) instance GHC.Show.Show a => GHC.Show.Show (Agda.Utils.Bag.Bag a) instance GHC.Classes.Ord a => GHC.Base.Monoid (Agda.Utils.Bag.Bag a) instance Data.Foldable.Foldable Agda.Utils.Bag.Bag instance (GHC.Classes.Ord a, Test.QuickCheck.Arbitrary.Arbitrary a) => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Utils.Bag.Bag a) -- | Utitlity functions on lists. module Agda.Utils.List -- | Case distinction for lists, with list first. Cf. ifNull. caseList :: [a] -> b -> (a -> [a] -> b) -> b -- | Case distinction for lists, with list last. listCase :: b -> (a -> [a] -> b) -> [a] -> b -- | Head function (safe). headMaybe :: [a] -> Maybe a -- | Head function (safe). Returns a value on empty lists. -- --
--   headWithDefault 42 []      = 42
--   headWithDefault 42 [1,2,3] = 1
--   
headWithDefault :: a -> [a] -> a -- | Last element (safe). lastMaybe :: [a] -> Maybe a -- | Opposite of cons (:), safe. uncons :: [a] -> Maybe (a, [a]) -- | Maybe cons. mcons ma as = maybeToList ma ++ as mcons :: Maybe a -> [a] -> [a] -- | init and last in one go, safe. initLast :: [a] -> Maybe ([a], a) -- | Lookup function (partially safe). (!!!) :: [a] -> Int -> Maybe a -- | downFrom n = [n-1,..1,0] downFrom :: Integral a => a -> [a] -- | Update the first element of a list, if it exists. updateHead :: (a -> a) -> [a] -> [a] spec_updateHead :: (a -> a) -> [a] -> [a] prop_updateHead :: Eq a => (a -> a) -> [a] -> Bool -- | Update the last element of a list, if it exists. updateLast :: (a -> a) -> [a] -> [a] spec_updateLast :: (a -> a) -> [a] -> [a] prop_updateLast :: Eq a => (a -> a) -> [a] -> Bool -- | Update nth element of a list, if it exists. Precondition: the index is -- >= 0. updateAt :: Int -> (a -> a) -> [a] -> [a] spec_updateAt :: Int -> (a -> a) -> [a] -> [a] prop_updateAt :: Eq a => NonNegative Int -> (a -> a) -> [a] -> Bool -- | A generalized version of partition. (Cf. mapMaybe -- vs. filter). mapEither :: (a -> Either b c) -> [a] -> ([b], [c]) deal :: (a -> Either b c) -> a -> ([b], [c]) -> ([b], [c]) -- | A generalized version of takeWhile. (Cf. mapMaybe -- vs. filter). takeWhileJust :: (a -> Maybe b) -> [a] -> [b] -- | A generalized version of span. spanJust :: (a -> Maybe b) -> [a] -> ([b], [a]) -- | Partition a list into Nothings and Justs. -- mapMaybe f = snd . partitionMaybe f. partitionMaybe :: (a -> Maybe b) -> [a] -> ([a], [b]) -- | Sublist relation. isSublistOf :: Eq a => [a] -> [a] -> Bool type Prefix a = [a] type Suffix a = [a] -- | Check if a list has a given prefix. If so, return the list minus the -- prefix. maybePrefixMatch :: Eq a => Prefix a -> [a] -> Maybe (Suffix a) -- | Result of preOrSuffix. data PreOrSuffix a -- | First list is prefix of second. IsPrefix :: a -> [a] -> PreOrSuffix a -- | First list is suffix of second. IsSuffix :: a -> [a] -> PreOrSuffix a -- | The lists are equal. IsBothfix :: PreOrSuffix a -- | The lists are incomparable. IsNofix :: PreOrSuffix a -- | Compare lists with respect to prefix partial order. preOrSuffix :: Eq a => [a] -> [a] -> PreOrSuffix a -- | Split a list into sublists. Generalisation of the prelude function -- words. -- --
--   words xs == wordsBy isSpace xs
--   
wordsBy :: (a -> Bool) -> [a] -> [[a]] -- | Chop up a list in chunks of a given length. chop :: Int -> [a] -> [[a]] -- | All ways of removing one element from a list. holes :: [a] -> [(a, [a])] -- | Check whether a list is sorted. -- -- Assumes that the Ord instance implements a partial order. sorted :: Ord a => [a] -> Bool -- | Check whether all elements in a list are distinct from each other. -- Assumes that the Eq instance stands for an equivalence -- relation. distinct :: Eq a => [a] -> Bool -- | An optimised version of distinct. -- -- Precondition: The list's length must fit in an Int. fastDistinct :: Ord a => [a] -> Bool prop_distinct_fastDistinct :: [Integer] -> Bool -- | Checks if all the elements in the list are equal. Assumes that the -- Eq instance stands for an equivalence relation. allEqual :: Eq a => [a] -> Bool -- | Returns an (arbitrary) representative for each list element that -- occurs more than once. duplicates :: Ord a => [a] -> [a] -- | A variant of groupBy which applies the predicate to consecutive -- pairs. groupBy' :: (a -> a -> Bool) -> [a] -> [[a]] prop_groupBy' :: (Bool -> Bool -> Bool) -> [Bool] -> Property -- | groupOn f = groupBy ((==) `on` f) . -- sortBy (compare `on` f). groupOn :: Ord b => (a -> b) -> [a] -> [[a]] -- | splitExactlyAt n xs = Just (ys, zs) iff xs = ys ++ -- zs and genericLength ys = n. splitExactlyAt :: Integral n => n -> [a] -> Maybe ([a], [a]) -- | extractNthElement n xs gives the n-th element -- in xs (counting from 0), plus the remaining elements -- (preserving order). extractNthElement' :: Integral i => i -> [a] -> ([a], a, [a]) extractNthElement :: Integral i => i -> [a] -> (a, [a]) prop_extractNthElement :: Integer -> [Integer] -> Property -- | A generalised variant of elemIndex. genericElemIndex :: (Eq a, Integral i) => a -> [a] -> Maybe i prop_genericElemIndex :: Integer -> [Integer] -> Property -- | Requires both lists to have the same length. zipWith' :: (a -> b -> c) -> [a] -> [b] -> [c] prop_zipWith' :: (Integer -> Integer -> Integer) -> Property -- | Efficient version of nub that sorts the list via a search tree -- (Map). uniqOn :: Ord b => (a -> b) -> [a] -> [a] prop_uniqOn :: [Integer] -> Bool -- | Compute the common suffix of two lists. commonSuffix :: Eq a => [a] -> [a] -> [a] -- | Compute the common prefix of two lists. commonPrefix :: Eq a => [a] -> [a] -> [a] prop_commonPrefix :: [Integer] -> [Integer] -> [Integer] -> Bool prop_commonSuffix :: [Integer] -> [Integer] -> [Integer] -> Bool tests :: IO Bool module Agda.Utils.String -- | quote adds double quotes around the string, replaces newline -- characters with n, and escapes double quotes and backslashes -- within the string. This is different from the behaviour of -- show: -- --
--   > putStrLn $ show "\x2200"
--   "\8704"
--   > putStrLn $ quote "\x2200"
--   "∀"
--   
-- -- (The code examples above have been tested using version 4.2.0.0 of the -- base library.) quote :: String -> String -- | Shows a non-negative integer using the characters ₀-₉ instead of 0-9. showIndex :: (Show i, Integral i) => i -> String -- | Adds a final newline if there is not already one. addFinalNewLine :: String -> String -- | Indents every line the given number of steps. indent :: Integral i => i -> String -> String newtype Str Str :: String -> Str [unStr] :: Str -> String -- | Show a number using comma to separate powers of 1,000. showThousandSep :: Show a => a -> String -- | Remove leading whitespace. ltrim :: String -> String -- | Remove trailing whitespace. rtrim :: String -> String -- | Remove leading and trailing whitesapce. trim :: String -> String instance GHC.Classes.Eq Agda.Utils.String.Str instance GHC.Show.Show Agda.Utils.String.Str -- | Examples how to use Agda.Utils.Lens. module Agda.Utils.Lens.Examples data Record a b Record :: a -> b -> Record a b [field1] :: Record a b -> a [field2] :: Record a b -> b -- | (View source:) This is how you implement a lens for a record field. lensField1 :: Lens' a (Record a b) lensField2 :: Lens' b (Record a b) -- | Wrapper for Control.Monad.Except from the mtl package module Agda.Utils.Except class Error a where noMsg = strMsg "" strMsg _ = noMsg noMsg :: Error a => a strMsg :: Error a => String -> a -- | A monad transformer that adds exceptions to other monads. -- -- ExceptT constructs a monad parameterized over two things: -- -- -- -- The return function yields a computation that produces the -- given value, while >>= sequences two subcomputations, -- exiting on the first exception. data ExceptT e (m :: * -> *) a :: * -> (* -> *) -> * -> * -- | We cannot define data constructors synonymous, so we define the -- mkExceptT function to be used instead of the data constructor -- ExceptT. mkExceptT :: m (Either e a) -> ExceptT e m a class Monad m => MonadError e (m :: * -> *) | m -> e throwError :: MonadError e m => e -> m a catchError :: MonadError e m => m a -> (e -> m a) -> m a -- | The inverse of ExceptT. runExceptT :: ExceptT e m a -> m (Either e a) -- | Map the unwrapped computation using the given function. -- -- mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b instance Agda.Utils.Except.Error GHC.Base.String instance Agda.Utils.Except.Error () instance Agda.Utils.Except.Error (a, b, c) module Agda.Utils.Monad -- | Binary bind. (==<<) :: Monad m => (a -> b -> m c) -> (m a, m b) -> m c -- | when_ is just Control.Monad.when with a more general -- type. when_ :: Monad m => Bool -> m a -> m () -- | unless_ is just Control.Monad.unless with a more -- general type. unless_ :: Monad m => Bool -> m a -> m () whenM :: Monad m => m Bool -> m a -> m () unlessM :: Monad m => m Bool -> m a -> m () -- | Monadic if-then-else. ifM :: Monad m => m Bool -> m a -> m a -> m a -- |
--   ifNotM mc = ifM (not $ mc)
--   
ifNotM :: Monad m => m Bool -> m a -> m a -> m a -- | Lazy monadic conjunction. and2M :: Monad m => m Bool -> m Bool -> m Bool andM :: Monad m => [m Bool] -> m Bool -- | Lazy monadic disjunction. or2M :: Monad m => m Bool -> m Bool -> m Bool orM :: Monad m => [m Bool] -> m Bool -- | Lazy monadic disjunction with Either truth values. altM1 :: Monad m => (a -> m (Either err b)) -> [a] -> m (Either err b) -- | Generalized version of mapM_ :: Monad m => (a -> m ()) -> -- [a] -> m () Executes effects and collects results in -- left-to-right order. Works best with left-associative monoids. -- -- Note that there is an alternative -- --
--   mapM' f t = foldr mappend mempty $ mapM f t
--   
-- -- that collects results in right-to-left order (effects still -- left-to-right). It might be preferable for right associative monoids. mapM' :: (Foldable t, Monad m, Monoid b) => (a -> m b) -> t a -> m b -- | Generalized version of forM_ :: Monad m => [a] -> (a -> m -- ()) -> m () forM' :: (Foldable t, Monad m, Monoid b) => t a -> (a -> m b) -> m b type Cont r a = (a -> r) -> r -- | mapM for the continuation monad. Terribly useful. thread :: (a -> Cont r b) -> [a] -> Cont r [b] -- | Requires both lists to have the same lengths. zipWithM' :: Monad m => (a -> b -> m c) -> [a] -> [b] -> m [c] -- | A monadic version of mapMaybe :: (a -> Maybe b) -> -- [a] -> [b]. mapMaybeM :: (Monad m, Functor m) => (a -> m (Maybe b)) -> [a] -> m [b] -- | The for version of mapMaybeM. forMaybeM :: (Monad m, Functor m) => [a] -> (a -> m (Maybe b)) -> m [b] -- | A monadic version of dropWhile :: (a -> Bool) -> [a] -- -> [a]. dropWhileM :: Monad m => (a -> m Bool) -> [a] -> m [a] -- | Finally for the Error class. Errors in the finally part take -- precedence over prior errors. finally :: (Error e, MonadError e m) => m a -> m b -> m a -- | Bracket without failure. Typically used to preserve state. bracket_ :: Monad m => m a -> (a -> m c) -> m b -> m b -- | Restore state after computation. localState :: MonadState s m => m a -> m a readM :: (Error e, MonadError e m, Read a) => String -> m a -- | Conditional execution of Applicative expressions. For example, -- --
--   when debug (putStrLn "Debugging")
--   
-- -- will output the string Debugging if the Boolean value -- debug is True, and otherwise do nothing. when :: Applicative f => Bool -> f () -> f () -- | The reverse of when. unless :: Applicative f => Bool -> f () -> f () -- | Monads that also support choice and failure. class (Alternative m, Monad m) => MonadPlus (m :: * -> *) -- | the identity of mplus. It should also satisfy the equations -- --
--   mzero >>= f  =  mzero
--   v >> mzero   =  mzero
--   
mzero :: MonadPlus m => m a -- | an associative operation mplus :: MonadPlus m => m a -> m a -> m a -- | An infix synonym for fmap. -- --

Examples

-- -- Convert from a Maybe Int to a -- Maybe String using show: -- --
--   >>> show <$> Nothing
--   Nothing
--   
--   >>> show <$> Just 3
--   Just "3"
--   
-- -- Convert from an Either Int Int to -- an Either Int String using -- show: -- --
--   >>> show <$> Left 17
--   Left 17
--   
--   >>> show <$> Right 17
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> (*2) <$> [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> even <$> (2,2)
--   (2,True)
--   
(<$>) :: Functor f => (a -> b) -> f a -> f b -- | Sequential application. (<*>) :: Applicative f => forall a b. f (a -> b) -> f a -> f b -- | Replace all locations in the input with the same value. The default -- definition is fmap . const, but this may be -- overridden with a more efficient version. (<$) :: Functor f => forall a b. a -> f b -> f a modify' :: MonadState s m => (s -> s) -> m () -- | Overloaded null and empty for collections and -- sequences. module Agda.Utils.Null class Null a where null = (== empty) empty :: Null a => a -- | Satisfying null empty == True. null :: Null a => a -> Bool -- | A Maybe is null when it corresponds to the empty list. ifNull :: (Null a) => a -> b -> (a -> b) -> b ifNullM :: (Monad m, Null a) => m a -> m b -> (a -> m b) -> m b whenNull :: (Monad m, Null a) => a -> m () -> m () unlessNull :: (Monad m, Null a) => a -> (a -> m ()) -> m () whenNullM :: (Monad m, Null a) => m a -> m () -> m () unlessNullM :: (Monad m, Null a) => m a -> (a -> m ()) -> m () instance Agda.Utils.Null.Null () instance (Agda.Utils.Null.Null a, Agda.Utils.Null.Null b) => Agda.Utils.Null.Null (a, b) instance Agda.Utils.Null.Null Data.ByteString.Internal.ByteString instance Agda.Utils.Null.Null [a] instance Agda.Utils.Null.Null (Agda.Utils.Bag.Bag a) instance Agda.Utils.Null.Null (Data.IntMap.Base.IntMap a) instance Agda.Utils.Null.Null Data.IntSet.Base.IntSet instance Agda.Utils.Null.Null (Data.Map.Base.Map k a) instance Agda.Utils.Null.Null (Data.HashMap.Base.HashMap k a) instance Agda.Utils.Null.Null (Data.HashSet.HashSet a) instance Agda.Utils.Null.Null (Data.Sequence.Seq a) instance Agda.Utils.Null.Null (Data.Set.Base.Set a) instance Agda.Utils.Null.Null (GHC.Base.Maybe a) instance Agda.Utils.Null.Null Text.PrettyPrint.HughesPJ.Doc -- | Pretty printing functions. module Agda.Utils.Pretty -- | While Show is for rendering data in Haskell syntax, -- Pretty is for displaying data to the world, i.e., the user and -- the environment. -- -- Atomic data has no inner document structure, so just implement -- pretty as pretty a = text $ ... a .... class Pretty a where pretty = prettyPrec 0 prettyPrec = const pretty pretty :: Pretty a => a -> Doc prettyPrec :: Pretty a => Int -> a -> Doc -- | Use instead of show when printing to world. prettyShow :: Pretty a => a -> String -- | Space separated list of pretty things. prettyList :: Pretty a => [a] -> Doc pwords :: String -> [Doc] fwords :: String -> Doc mparens :: Bool -> Doc -> Doc -- | align max rows lays out the elements of rows in two -- columns, with the second components aligned. The alignment column of -- the second components is at most max characters to the right -- of the left-most column. -- -- Precondition: max > 0. align :: Int -> [(String, Doc)] -> Doc instance Agda.Utils.Pretty.Pretty GHC.Types.Bool instance Agda.Utils.Pretty.Pretty GHC.Types.Int instance Agda.Utils.Pretty.Pretty GHC.Int.Int32 instance Agda.Utils.Pretty.Pretty GHC.Integer.Type.Integer instance Agda.Utils.Pretty.Pretty GHC.Types.Char instance Agda.Utils.Pretty.Pretty Text.PrettyPrint.HughesPJ.Doc instance Agda.Utils.Pretty.Pretty GHC.Base.String -- | Operations on file names. module Agda.Utils.FileName -- | Paths which are known to be absolute. -- -- Note that the Eq and Ord instances do not check if -- different paths point to the same files or directories. -- -- Andreas, 2014-03-30: For efficiency of serialization, -- AbsolutePath is implemented as ByteString which -- short-cuts equality testing using pointer equality. This saves 20% of -- the serialization time of the standard library! data AbsolutePath -- | Extract the AbsolutePath to be used as FilePath. filePath :: AbsolutePath -> FilePath -- | maps blablablafoo.bar.xxx to foo.bar. rootName :: AbsolutePath -> String -- | Constructs AbsolutePaths. -- -- Precondition: The path must be absolute and valid. mkAbsolute :: FilePath -> AbsolutePath -- | Makes the path absolute. -- -- This function may raise an __IMPOSSIBLE__ error if -- canonicalizePath does not return an absolute path. absolute :: FilePath -> IO AbsolutePath -- | Tries to establish if the two file paths point to the same file (or -- directory). (===) :: AbsolutePath -> AbsolutePath -> Bool -- | Case-sensitive doesFileExist for Windows. This is case-sensitive only -- on the file name part, not on the directory part. (Ideally, path -- components coming from module name components should be checked -- case-sensitively and the other path components should be checked case -- insenstively.) doesFileExistCaseSensitive :: FilePath -> IO Bool tests :: IO Bool instance Data.Hashable.Class.Hashable Agda.Utils.FileName.AbsolutePath instance GHC.Classes.Ord Agda.Utils.FileName.AbsolutePath instance GHC.Classes.Eq Agda.Utils.FileName.AbsolutePath instance GHC.Show.Show Agda.Utils.FileName.AbsolutePath instance Agda.Utils.Pretty.Pretty Agda.Utils.FileName.AbsolutePath instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Utils.FileName.AbsolutePath -- | Instead of checking time-stamps we compute a hash of the module source -- and store it in the interface file. This module contains the functions -- to do that. module Agda.Utils.Hash type Hash = Word64 hashByteString :: ByteString -> Hash hashFile :: AbsolutePath -> IO Hash combineHashes :: [Hash] -> Hash -- | Hashing a module name for unique identifiers. hashString :: String -> Integer -- | Code for instructing Emacs to do things module Agda.Interaction.EmacsCommand -- | Simple Emacs Lisp expressions. data Lisp a -- | Atom. A :: a -> Lisp a Cons :: (Lisp a) -> (Lisp a) -> Lisp a -- | List. L :: [Lisp a] -> Lisp a Q :: (Lisp a) -> Lisp a -- | Formats a response command. -- -- Replaces '\n' with spaces to ensure that each command is a -- single line. response :: Lisp String -> String -- | Writes a response command to standard output. putResponse :: Lisp String -> IO () -- | display_info' append header content displays content -- (with header header) in some suitable way. If append -- is True, then the content is appended to previous content (if -- any), otherwise any previous content is deleted. display_info' :: Bool -> String -> String -> Lisp String -- | Clear the running info buffer. clearRunningInfo :: Lisp String -- | Display running information about what the type-checker is up to. displayRunningInfo :: String -> Lisp String instance Agda.Utils.Pretty.Pretty a => Agda.Utils.Pretty.Pretty (Agda.Interaction.EmacsCommand.Lisp a) instance Agda.Utils.Pretty.Pretty a => GHC.Show.Show (Agda.Interaction.EmacsCommand.Lisp a) -- | Time-related utilities. module Agda.Utils.Time -- | Timestamps. type ClockTime = UTCTime -- | The current time. getClockTime :: IO ClockTime getCPUTime :: MonadIO m => m CPUTime -- | Measure the time of a computation. Of course, does not work with -- exceptions. measureTime :: MonadIO m => m a -> m (a, CPUTime) -- | CPU time in pico (10^-12) seconds. newtype CPUTime CPUTime :: Integer -> CPUTime instance GHC.Real.Integral Agda.Utils.Time.CPUTime instance GHC.Enum.Enum Agda.Utils.Time.CPUTime instance GHC.Real.Real Agda.Utils.Time.CPUTime instance GHC.Num.Num Agda.Utils.Time.CPUTime instance GHC.Classes.Ord Agda.Utils.Time.CPUTime instance GHC.Show.Show Agda.Utils.Time.CPUTime instance GHC.Classes.Eq Agda.Utils.Time.CPUTime instance Agda.Utils.Pretty.Pretty Agda.Utils.Time.CPUTime -- | Collection size. -- -- For TermSize see Agda.Syntax.Internal. module Agda.Utils.Size -- | The size of a collection (i.e., its length). -- -- Should fit into an Int. TODO: change to Int. class Sized a size :: (Sized a, Integral n) => a -> n -- | Thing decorated with its size. The thing should fit into main memory, -- thus, the size is an Int. data SizedThing a SizedThing :: !Int -> a -> SizedThing a [theSize] :: SizedThing a -> !Int [sizedThing] :: SizedThing a -> a -- | Cache the size of an object. sizeThing :: Sized a => a -> SizedThing a instance Agda.Utils.Size.Sized [a] instance Agda.Utils.Size.Sized (Data.IntMap.Base.IntMap a) instance Agda.Utils.Size.Sized Data.IntSet.Base.IntSet instance Agda.Utils.Size.Sized (Data.Map.Base.Map k a) instance Agda.Utils.Size.Sized (Data.Set.Base.Set a) instance Agda.Utils.Size.Sized (Data.HashMap.Base.HashMap k a) instance Agda.Utils.Size.Sized (Data.HashSet.HashSet a) instance Agda.Utils.Size.Sized (Data.Sequence.Seq a) instance Agda.Utils.Size.Sized (Agda.Utils.Size.SizedThing a) instance Agda.Utils.Null.Null a => Agda.Utils.Null.Null (Agda.Utils.Size.SizedThing a) -- | Maintaining a list of favorites of some partially ordered type. Only -- the best elements are kept. -- -- To avoid name clashes, import this module qualified, as in import -- Agda.Utils.Favorites (Favorites) import qualified Agda.Utils.Favorites -- as Fav module Agda.Utils.Favorites -- | A list of incomparable favorites. newtype Favorites a Favorites :: [a] -> Favorites a [toList] :: Favorites a -> [a] -- | Equality checking is a bit expensive, since we need to sort! Maybe use -- a Set of favorites in the first place? -- | Result of comparing a candidate with the current favorites. data CompareResult a -- | Great, you are dominating a possibly (empty list of favorites) but -- there is also a rest that is not dominated. If null -- dominated, then notDominated is necessarily the complete -- list of favorites. Dominates :: [a] -> [a] -> CompareResult a [dominated] :: CompareResult a -> [a] [notDominated] :: CompareResult a -> [a] -- | Sorry, but you are dominated by that favorite. IsDominated :: a -> CompareResult a [dominator] :: CompareResult a -> a -- | Gosh, got some pretty a here, compare with my current -- favorites! Discard it if there is already one that is better or equal. -- (Skewed conservatively: faithful to the old favorites.) If there is no -- match for it, add it, and dispose of all that are worse than -- a. -- -- We require a partial ordering. Less is better! (Maybe paradoxically.) compareWithFavorites :: PartialOrd a => a -> Favorites a -> CompareResult a -- | Compare a new set of favorites to an old one and discard the new -- favorites that are dominated by the old ones and vice verse. (Skewed -- conservatively: faithful to the old favorites.) -- --
--   compareFavorites new old = (new', old')
--   
compareFavorites :: PartialOrd a => Favorites a -> Favorites a -> (Favorites a, Favorites a) unionCompared :: PartialOrd a => (Favorites a, Favorites a) -> Favorites a -- | After comparing, do the actual insertion. insertCompared :: PartialOrd a => a -> Favorites a -> CompareResult a -> Favorites a -- | Compare, then insert accordingly. insert a l = insertCompared a l -- (compareWithFavorites a l) insert :: PartialOrd a => a -> Favorites a -> Favorites a -- | Insert all the favorites from the first list into the second. union :: PartialOrd a => Favorites a -> Favorites a -> Favorites a -- | Construct favorites from elements of a partial order. The result -- depends on the order of the list if it contains equal elements, since -- earlier seen elements are favored over later seen equals. The first -- element of the list is seen first. fromList :: PartialOrd a => [a] -> Favorites a -- | Favorites forms a Monoid under empty and 'union. property_null_empty :: Bool property_not_null_singleton :: a -> Bool prop_compareWithFavorites :: ISet -> Favorites ISet -> Bool prop_fromList_after_toList :: Favorites ISet -> Bool -- | A second way to compute the union is to use -- compareFavorites. prop_union_union2 :: Favorites ISet -> Favorites ISet -> Bool -- | All tests as collected by quickCheckAll. -- -- Using quickCheckAll is convenient and superior to the manual -- enumeration of tests, since the name of the property is added -- automatically. tests :: IO Bool instance Agda.Utils.Singleton.Singleton a (Agda.Utils.Favorites.Favorites a) instance Agda.Utils.Null.Null (Agda.Utils.Favorites.Favorites a) instance Test.QuickCheck.Arbitrary.CoArbitrary a => Test.QuickCheck.Arbitrary.CoArbitrary (Agda.Utils.Favorites.Favorites a) instance GHC.Show.Show a => GHC.Show.Show (Agda.Utils.Favorites.Favorites a) instance Data.Foldable.Foldable Agda.Utils.Favorites.Favorites instance GHC.Classes.Ord a => GHC.Classes.Eq (Agda.Utils.Favorites.Favorites a) instance Agda.Utils.PartialOrd.PartialOrd a => GHC.Base.Monoid (Agda.Utils.Favorites.Favorites a) instance (Agda.Utils.PartialOrd.PartialOrd a, Test.QuickCheck.Arbitrary.Arbitrary a) => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Utils.Favorites.Favorites a) -- | Directed graphs (can of course simulate undirected graphs). -- -- Represented as adjacency maps in direction from source to target. -- -- Each source node maps to a adjacency map of outgoing edges, which is a -- map from target nodes to edges. -- -- This allows to get outgoing edges in O(log n) time where n is -- the number of nodes in the graph. -- -- However, the set of incoming edges can only be obtained in O(n log -- n) or O(e) where e is the total number of -- edges. module Agda.Utils.Graph.AdjacencyMap.Unidirectional -- | Graph s t e is a directed graph with source nodes in -- s target nodes in t and edges in e. -- -- Admits at most one edge between any two nodes. Several edges can be -- modeled by using a collection type for e. -- -- Represented as "adjacency list", or rather, adjacency map. This allows -- to get all outgoing edges for a node in O(log n) time where -- n is the number of nodes of the graph. -- -- Incoming edges can only be computed in O(n + e) time where -- e is the number of edges. newtype Graph s t e Graph :: Map s (Map t e) -> Graph s t e -- | Forward edges. [graph] :: Graph s t e -> Map s (Map t e) data Edge s t e Edge :: s -> t -> e -> Edge s t e -- | Outgoing node. [source] :: Edge s t e -> s -- | Incoming node. [target] :: Edge s t e -> t -- | Edge label (weight). [label] :: Edge s t e -> e -- | Reverse an edge. transposeEdge :: Edge s t e -> Edge t s e -- | Turn a graph into a list of edges. O(n + e) edges :: (Ord s, Ord t) => Graph s t e -> [Edge s t e] -- | All edges originating in the given nodes. (I.e., all outgoing edges -- for the given nodes.) -- -- Roughly linear in the length of the result list O(result). edgesFrom :: (Ord s, Ord t) => Graph s t e -> [s] -> [Edge s t e] -- | All edges ending in the given nodes. (I.e., all incoming edges for the -- given nodes.) -- -- Expensive: O(n * |ts| * log n). edgesTo :: (Ord s, Ord t) => Graph s t e -> [t] -> [Edge s t e] -- | Get all self-loops. diagonal :: (Ord n) => Graph n n e -> [Edge n n e] -- | Lookup label of an edge. lookup :: (Ord s, Ord t) => s -> t -> Graph s t e -> Maybe e -- | Get a list of outgoing edges with target. neighbours :: (Ord s, Ord t) => s -> Graph s t e -> [(t, e)] -- | Get a list of outgoing edges with target. neighboursMap :: (Ord s, Ord t) => s -> Graph s t e -> Map t e -- | Returns all the nodes with outgoing edges. O(n). sourceNodes :: (Ord s, Ord t) => Graph s t e -> Set s -- | Returns all the nodes with incoming edges. Expensive! O(e). targetNodes :: (Ord s, Ord t) => Graph s t e -> Set t -- | For homogeneous graphs, (s = t) we can compute a set of all -- nodes. -- -- Structure Nodes is for computing all nodes but also -- remembering which were incoming and which outgoing. This is mostly for -- efficiency reasons, to avoid recomputation when all three sets are -- needed. data Nodes n Nodes :: Set n -> Set n -> Set n -> Nodes n [srcNodes] :: Nodes n -> Set n [tgtNodes] :: Nodes n -> Set n [allNodes] :: Nodes n -> Set n computeNodes :: (Ord n) => Graph n n e -> Nodes n -- | The set of all nodes (outgoing and incoming). nodes :: (Ord n) => Graph n n e -> Set n -- | Constructs a completely disconnected graph containing the given nodes. -- O(n). fromNodes :: Ord n => [n] -> Graph n n e -- | Constructs a graph from a list of edges. O(e log n) -- -- Later edges overwrite earlier edges. fromList :: (Ord s, Ord t) => [Edge s t e] -> Graph s t e -- | Constructs a graph from a list of edges. O(e log n) -- -- Later edges are combined with earlier edges using the supplied -- function. fromListWith :: (Ord s, Ord t) => (e -> e -> e) -> [Edge s t e] -> Graph s t e -- | Convert a graph into a list of edges. O(e) toList :: (Ord s, Ord t) => Graph s t e -> [Edge s t e] -- | Check whether the graph is discrete (no edges). This could be seen as -- an empty graph. Worst-case (is discrete): O(e). discrete :: Null e => Graph s t e -> Bool -- | Remove Null edges. clean :: (Ord s, Ord t, Null e) => Graph s t e -> Graph s t e -- | Empty graph (no nodes, no edges). empty :: Graph s t e -- | A graph with two nodes and a single connecting edge. singleton :: (Ord s, Ord t) => s -> t -> e -> Graph s t e -- | Insert an edge into the graph. insert :: (Ord s, Ord t) => s -> t -> e -> Graph s t e -> Graph s t e -- | Insert an edge, possibly combining old edge weight with -- new weight by given function f into f new -- old. insertWith :: (Ord s, Ord t) => (e -> e -> e) -> s -> t -> e -> Graph s t e -> Graph s t e insertEdge :: (Ord s, Ord t) => Edge s t e -> Graph s t e -> Graph s t e insertEdgeWith :: (Ord s, Ord t) => (e -> e -> e) -> Edge s t e -> Graph s t e -> Graph s t e -- | Left-biased union. union :: (Ord s, Ord t) => Graph s t e -> Graph s t e -> Graph s t e unionWith :: (Ord s, Ord t) => (e -> e -> e) -> Graph s t e -> Graph s t e -> Graph s t e unions :: (Ord s, Ord t) => [Graph s t e] -> Graph s t e unionsWith :: (Ord s, Ord t) => (e -> e -> e) -> [Graph s t e] -> Graph s t e -- | Removes the given node, be it source or target, and all corresponding -- edges, from the graph. -- -- Expensive! O(n log n). removeNode :: Ord n => n -> Graph n n e -> Graph n n e -- | removeEdge s t g removes the edge going from s to -- t, if any. -- -- O((log n)^2). removeEdge :: (Ord s, Ord t) => s -> t -> Graph s t e -> Graph s t e -- | Keep only the edges that satisfy the predicate. O(e). filterEdges :: (Ord s, Ord t) => (e -> Bool) -> Graph s t e -> Graph s t e -- | Unzipping a graph (naive implementation using fmap). unzip :: Graph s t (e, e') -> (Graph s t e, Graph s t e') -- | Maps over a graph under availability of positional information, like -- mapWithKey. mapWithEdge :: (Ord s, Ord t) => (Edge s t e -> e') -> Graph s t e -> Graph s t e' -- | The graph's strongly connected components, in reverse topological -- order. sccs' :: Ord n => Graph n n e -> [SCC n] -- | The graph's strongly connected components, in reverse topological -- order. sccs :: Ord n => Graph n n e -> [[n]] -- | SCC DAGs. -- -- The maps map SCC indices to and from SCCs/nodes. data DAG n DAG :: Graph -> IntMap (SCC n) -> Map n Int -> DAG n [dagGraph] :: DAG n -> Graph [dagComponentMap] :: DAG n -> IntMap (SCC n) [dagNodeMap] :: DAG n -> Map n Int -- | DAG invariant. dagInvariant :: Ord n => DAG n -> Bool -- | The opposite DAG. oppositeDAG :: DAG n -> DAG n -- | The nodes reachable from the given SCC. reachable :: Ord n => DAG n -> SCC n -> [n] -- | Constructs a DAG containing the graph's strongly connected components. sccDAG' :: Ord n => Graph n n e -> [SCC n] -> DAG n -- | Constructs a DAG containing the graph's strongly connected components. sccDAG :: Ord n => Graph n n e -> DAG n -- | Returns True iff the graph is acyclic. acyclic :: Ord n => Graph n n e -> Bool -- | composeWith times plus g g' finds all edges s --c_i--> -- t_i --d_i--> u and constructs the result graph from -- edge(s,u) = sum_i (c_i times d_i). -- -- Complexity: for each edge s --> t in g we lookup -- up all edges starting in with t in g'. composeWith :: (Ord s, Ord t, Ord u) => (c -> d -> e) -> (e -> e -> e) -> Graph s t c -> Graph t u d -> Graph s u e -- | Transitive closure ported from Agda.Termination.CallGraph. -- -- Relatively efficient, see Issue 1560. complete :: (Eq e, Null e, SemiRing e, Ord n) => Graph n n e -> Graph n n e -- | Computes the transitive closure of the graph. -- -- Uses the Gauss-Jordan-Floyd-Warshall-McNaughton-Yamada algorithm (as -- described by Russell O'Connor in "A Very General Method of Computing -- Shortest Paths" http://r6.ca/blog/20110808T035622Z.html), -- implemented using matrices. -- -- The resulting graph does not contain any zero edges. -- -- This algorithm should be seen as a reference implementation. In -- practice gaussJordanFloydWarshallMcNaughtonYamada is likely to -- be more efficient. gaussJordanFloydWarshallMcNaughtonYamadaReference :: (Ord n, Eq e, StarSemiRing e) => Graph n n e -> Graph n n e -- | Computes the transitive closure of the graph. -- -- Uses the Gauss-Jordan-Floyd-Warshall-McNaughton-Yamada algorithm (as -- described by Russell O'Connor in "A Very General Method of Computing -- Shortest Paths" http://r6.ca/blog/20110808T035622Z.html), -- implemented using Graph, and with some shortcuts: -- -- gaussJordanFloydWarshallMcNaughtonYamada :: (Ord n, Eq e, StarSemiRing e) => Graph n n e -> Graph n n e -- | Find a path from a source node to a target node. -- -- The path must satisfy the given predicate good :: e -> -- Bool. findPath :: (SemiRing e, Ord n) => (e -> Bool) -> n -> n -> Graph n n e -> Maybe e -- | allPaths classify a b g returns a list of pathes (accumulated -- edge weights) from node a to node b in g. -- Alternative intermediate pathes are only considered if they are -- distinguished by the classify function. allPaths :: (SemiRing e, Ord n, Ord c) => (e -> c) -> n -> n -> Graph n n e -> [e] instance (GHC.Show.Show s, GHC.Show.Show t, GHC.Show.Show e) => GHC.Show.Show (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Edge s t e) instance GHC.Base.Functor (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Edge s t) instance (GHC.Classes.Ord s, GHC.Classes.Ord t, GHC.Classes.Ord e) => GHC.Classes.Ord (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Edge s t e) instance (GHC.Classes.Eq s, GHC.Classes.Eq t, GHC.Classes.Eq e) => GHC.Classes.Eq (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Edge s t e) instance (GHC.Show.Show s, GHC.Show.Show t, GHC.Show.Show e) => GHC.Show.Show (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Graph s t e) instance GHC.Base.Functor (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Graph s t) instance (GHC.Classes.Eq s, GHC.Classes.Eq t, GHC.Classes.Eq e) => GHC.Classes.Eq (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Graph s t e) instance (Test.QuickCheck.Arbitrary.Arbitrary s, Test.QuickCheck.Arbitrary.Arbitrary t, Test.QuickCheck.Arbitrary.Arbitrary e) => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Edge s t e) instance (Test.QuickCheck.Arbitrary.CoArbitrary s, Test.QuickCheck.Arbitrary.CoArbitrary t, Test.QuickCheck.Arbitrary.CoArbitrary e) => Test.QuickCheck.Arbitrary.CoArbitrary (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Edge s t e) instance (GHC.Classes.Ord n, Agda.Utils.SemiRing.SemiRing e, Test.QuickCheck.Arbitrary.Arbitrary n, Test.QuickCheck.Arbitrary.Arbitrary e) => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Graph n n e) module Agda.TypeChecking.SizedTypes.WarshallSolver type Graph r f a = Graph (Node r f) (Node r f) a type Edge' r f a = Edge (Node r f) (Node r f) a type Key r f = Edge' r f () type Nodes r f = Nodes (Node r f) type LabelledEdge r f = Edge' r f Label src :: Edge s t e -> s dest :: Edge s t e -> t lookupEdge :: (Ord s, Ord t) => Graph s t e -> s -> t -> Maybe e graphToList :: (Ord s, Ord t) => Graph s t e -> [Edge s t e] graphFromList :: (Ord s, Ord t) => [Edge s t e] -> Graph s t e insertEdge :: (Ord s, Ord t, MeetSemiLattice e, Top e) => Edge s t e -> Graph s t e -> Graph s t e -- | Compute list of edges that start in a given node. outgoing :: (Ord r, Ord f) => Graph r f a -> Node r f -> [Edge' r f a] -- | Compute list of edges that target a given node. -- -- Note: expensive for unidirectional graph representations. incoming :: (Ord r, Ord f) => Graph r f a -> Node r f -> [Edge' r f a] -- | Set.foldl does not exist in legacy versions of the -- containers package. setFoldl :: (b -> a -> b) -> b -> Set a -> b -- | Floyd-Warshall algorithm. transClos :: (Ord n, Dioid a) => Graph n n a -> Graph n n a data Weight Offset :: Offset -> Weight Infinity :: Weight -- | Partial implementation of Num. -- | Test for negativity, used to detect negative cycles. class Negative a negative :: Negative a => a -> Bool -- | Going from Lt to Le is pred, going from -- Le to Lt is succ. -- -- X --(R,n)--> Y means X (R) Y + n. [ ... if -- n positive and X + (-n) (R) Y if n -- negative. ] data Label Label :: Cmp -> Offset -> Label [lcmp] :: Label -> Cmp [loffset] :: Label -> Offset -- | Nodes not connected. LInf :: Label -- | Convert a label to a weight, decrementing in case of Lt. toWeight :: Label -> Weight data Node rigid flex NodeZero :: Node rigid flex NodeInfty :: Node rigid flex NodeRigid :: rigid -> Node rigid flex NodeFlex :: flex -> Node rigid flex isFlexNode :: Node rigid flex -> Maybe flex isZeroNode :: Node rigid flex -> Bool isInftyNode :: Node rigid flex -> Bool nodeToSizeExpr :: Node rigid flex -> SizeExpr' rigid flex -- | An edge is negative if its label is. -- | A graph forest. type Graphs r f a = [Graph r f a] emptyGraphs :: Graphs r f a -- | Split a list of graphs gs into those that mention node -- n and those that do not. If n is zero or infinity, -- we regard it as "not mentioned". mentions :: (Ord r, Ord f) => Node r f -> Graphs r f a -> (Graphs r f a, Graphs r f a) -- | Add an edge to a graph forest. Graphs that share a node with the edge -- are joined. addEdge :: (Ord r, Ord f, MeetSemiLattice a, Top a) => Edge' r f a -> Graphs r f a -> Graphs r f a -- | Reflexive closure. Add edges 0 -> n -> n -> oo for -- all nodes n. reflClos :: (Ord r, Ord f, Show a, Dioid a) => Set (Node r f) -> Graph r f a -> Graph r f a -- | A graph is negative if it contains a negative loop (diagonal -- edge). Makes sense on transitive graphs. -- | h implies g if any edge in g between rigids -- and constants is implied by a corresponding edge in h, which -- means that the edge in g carries at most the information of -- the one in h. -- -- Application: Constraint implication: Constraints are compatible with -- hypotheses. implies :: (Ord r, Ord f, Show r, Show f, Show a, Top a, Ord a, Negative a) => Graph r f a -> Graph r f a -> Bool nodeFromSizeExpr :: SizeExpr' rigid flex -> (Node rigid flex, Offset) edgeFromConstraint :: Constraint' rigid flex -> LabelledEdge rigid flex -- | Build a graph from list of simplified constraints. graphFromConstraints :: (Ord rigid, Ord flex) => [Constraint' rigid flex] -> Graph rigid flex Label -- | Build a graph from list of simplified constraints. graphsFromConstraints :: (Ord rigid, Ord flex) => [Constraint' rigid flex] -> Graphs rigid flex Label type Hyp = Constraint type Hyp' = Constraint' type HypGraph r f = Graph r f Label hypGraph :: (Ord rigid, Ord flex) => Set rigid -> [Hyp' rigid flex] -> Maybe (HypGraph rigid flex) hypConn :: (Ord r, Ord f) => HypGraph r f -> Node r f -> Node r f -> Label simplifyWithHypotheses :: (Ord rigid, Ord flex) => HypGraph rigid flex -> [Constraint' rigid flex] -> Maybe [Constraint' rigid flex] type ConGraph r f = Graph r f Label constraintGraph :: (Ord r, Ord f, Show r, Show f) => [Constraint' r f] -> HypGraph r f -> Maybe (ConGraph r f) type ConGraphs r f = Graphs r f Label constraintGraphs :: (Ord r, Ord f, Show r, Show f) => [Constraint' r f] -> HypGraph r f -> Maybe ([f], ConGraphs r f) -- | If we have an edge X + n <= X (with n >= 0), we must -- set X = oo. infinityFlexs :: (Ord r, Ord f) => ConGraph r f -> ([f], ConGraph r f) class SetToInfty f a setToInfty :: SetToInfty f a => [f] -> a -> a -- | Lower or upper bound for a flexible variable type Bound r f = Map f (Set (SizeExpr' r f)) emptyBound :: Bound r f data Bounds r f Bounds :: Bound r f -> Bound r f -> Set f -> Bounds r f [lowerBounds] :: Bounds r f -> Bound r f [upperBounds] :: Bounds r f -> Bound r f [mustBeFinite] :: Bounds r f -> Set f -- | Compute a lower bound for a flexible from an edge. edgeToLowerBound :: (Ord r, Ord f) => LabelledEdge r f -> Maybe (f, SizeExpr' r f) -- | Compute an upper bound for a flexible from an edge. edgeToUpperBound :: (Ord r, Ord f) => LabelledEdge r f -> Maybe (f, Cmp, SizeExpr' r f) -- | Compute the lower bounds for all flexibles in a graph. graphToLowerBounds :: (Ord r, Ord f) => [LabelledEdge r f] -> Bound r f -- | Compute the upper bounds for all flexibles in a graph. graphToUpperBounds :: (Ord r, Ord f) => [LabelledEdge r f] -> (Bound r f, Set f) -- | Compute the bounds for all flexibles in a graph. bounds :: (Ord r, Ord f) => ConGraph r f -> Bounds r f -- | Compute the relative minima in a set of nodes (those that do not have -- a predecessor in the set). smallest :: (Ord r, Ord f) => HypGraph r f -> [Node r f] -> [Node r f] -- | Compute the relative maxima in a set of nodes (those that do not have -- a successor in the set). largest :: (Ord r, Ord f) => HypGraph r f -> [Node r f] -> [Node r f] -- | Given source nodes n1,n2,... find all target nodes m1,m2, such that -- for all j, there are edges n_i --l_ij--> m_j for all i. Return -- these edges as a map from target notes to a list of edges. We assume -- the graph is reflexive-transitive. commonSuccs :: (Ord r, Ord f, Dioid a) => Graph r f a -> [Node r f] -> Map (Node r f) [Edge' r f a] -- | Given target nodes m1,m2,... find all source nodes n1,n2, such that -- for all j, there are edges n_i --l_ij--> m_j for all i. Return -- these edges as a map from target notes to a list of edges. We assume -- the graph is reflexive-transitive. commonPreds :: (Ord r, Ord f, Dioid a) => Graph r f a -> [Node r f] -> Map (Node r f) [Edge' r f a] -- | Compute the sup of two different rigids or a rigid and a constant. lub' :: (Ord r, Ord f, Show r, Show f) => HypGraph r f -> (Node r f, Offset) -> (Node r f, Offset) -> Maybe (SizeExpr' r f) -- | Compute the inf of two different rigids or a rigid and a constant. glb' :: (Ord r, Ord f, Show r, Show f) => HypGraph r f -> (Node r f, Offset) -> (Node r f, Offset) -> Maybe (SizeExpr' r f) -- | Compute the least upper bound (sup). lub :: (Ord r, Ord f, Show r, Show f) => HypGraph r f -> (SizeExpr' r f) -> (SizeExpr' r f) -> Maybe (SizeExpr' r f) -- | Compute the greatest lower bound (inf) of size expressions relative to -- a hypotheses graph. glb :: (Ord r, Ord f, Show r, Show f) => HypGraph r f -> (SizeExpr' r f) -> (SizeExpr' r f) -> Maybe (SizeExpr' r f) findRigidBelow :: (Ord r, Ord f, Show r, Show f) => HypGraph r f -> (SizeExpr' r f) -> Maybe (SizeExpr' r f) solveGraph :: (Ord r, Ord f, Show r, Show f) => Polarities f -> HypGraph r f -> ConGraph r f -> Either String (Solution r f) -- | Solve a forest of constraint graphs relative to a hypotheses graph. -- Concatenate individual solutions. solveGraphs :: (Ord r, Ord f, Show r, Show f) => Polarities f -> HypGraph r f -> ConGraphs r f -> Either String (Solution r f) -- | Check that after substitution of the solution, constraints are implied -- by hypotheses. verifySolution :: (Ord r, Ord f, Show r, Show f) => HypGraph r f -> [Constraint' r f] -> Solution r f -> Either String () testSuccs :: Ord f => Map (Node [Char] f) [Edge' [Char] f Label] testLub :: (Show f, Ord f) => Maybe (SizeExpr' [Char] f) instance (GHC.Classes.Ord rigid, GHC.Classes.Ord flex) => GHC.Classes.Ord (Agda.TypeChecking.SizedTypes.WarshallSolver.Node rigid flex) instance (GHC.Classes.Eq rigid, GHC.Classes.Eq flex) => GHC.Classes.Eq (Agda.TypeChecking.SizedTypes.WarshallSolver.Node rigid flex) instance GHC.Classes.Eq Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance GHC.Show.Show Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance GHC.Classes.Ord Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance Agda.TypeChecking.SizedTypes.Utils.MeetSemiLattice Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance Agda.TypeChecking.SizedTypes.Utils.Top Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance GHC.Enum.Enum Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance GHC.Num.Num Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance Agda.TypeChecking.SizedTypes.Utils.Plus Agda.TypeChecking.SizedTypes.WarshallSolver.Weight Agda.TypeChecking.SizedTypes.Syntax.Offset Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance Test.QuickCheck.Arbitrary.Arbitrary Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance Agda.TypeChecking.SizedTypes.WarshallSolver.Negative GHC.Types.Int instance Agda.TypeChecking.SizedTypes.WarshallSolver.Negative Agda.TypeChecking.SizedTypes.Syntax.Offset instance Agda.TypeChecking.SizedTypes.WarshallSolver.Negative Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance Agda.TypeChecking.SizedTypes.WarshallSolver.Negative Agda.TypeChecking.SizedTypes.WarshallSolver.Label instance GHC.Classes.Eq Agda.TypeChecking.SizedTypes.WarshallSolver.Label instance GHC.Classes.Ord Agda.TypeChecking.SizedTypes.WarshallSolver.Label instance GHC.Show.Show Agda.TypeChecking.SizedTypes.WarshallSolver.Label instance Agda.TypeChecking.SizedTypes.Utils.MeetSemiLattice Agda.TypeChecking.SizedTypes.WarshallSolver.Label instance Agda.TypeChecking.SizedTypes.Utils.Top Agda.TypeChecking.SizedTypes.WarshallSolver.Label instance Test.QuickCheck.Arbitrary.Arbitrary Agda.TypeChecking.SizedTypes.WarshallSolver.Label instance Agda.TypeChecking.SizedTypes.Utils.Dioid Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance Agda.TypeChecking.SizedTypes.Utils.Dioid Agda.TypeChecking.SizedTypes.WarshallSolver.Label instance (GHC.Show.Show rigid, GHC.Show.Show flex) => GHC.Show.Show (Agda.TypeChecking.SizedTypes.WarshallSolver.Node rigid flex) instance Agda.TypeChecking.SizedTypes.WarshallSolver.Negative a => Agda.TypeChecking.SizedTypes.WarshallSolver.Negative (Agda.TypeChecking.SizedTypes.WarshallSolver.Edge' r f a) instance (GHC.Show.Show r, GHC.Show.Show f, GHC.Show.Show a, GHC.Classes.Ord r, GHC.Classes.Ord f, Agda.TypeChecking.SizedTypes.Utils.MeetSemiLattice a) => Agda.TypeChecking.SizedTypes.Utils.MeetSemiLattice (Agda.TypeChecking.SizedTypes.WarshallSolver.Edge' r f a) instance (GHC.Classes.Ord r, GHC.Classes.Ord f, Agda.TypeChecking.SizedTypes.Utils.Top a) => Agda.TypeChecking.SizedTypes.Utils.Top (Agda.TypeChecking.SizedTypes.WarshallSolver.Edge' r f a) instance (GHC.Show.Show r, GHC.Show.Show f, GHC.Show.Show a, GHC.Classes.Ord r, GHC.Classes.Ord f, Agda.TypeChecking.SizedTypes.Utils.Dioid a) => Agda.TypeChecking.SizedTypes.Utils.Dioid (Agda.TypeChecking.SizedTypes.WarshallSolver.Edge' r f a) instance (GHC.Classes.Ord r, GHC.Classes.Ord f, Agda.TypeChecking.SizedTypes.WarshallSolver.Negative a) => Agda.TypeChecking.SizedTypes.WarshallSolver.Negative (Agda.TypeChecking.SizedTypes.WarshallSolver.Graph r f a) instance (GHC.Classes.Ord r, GHC.Classes.Ord f, Agda.TypeChecking.SizedTypes.WarshallSolver.Negative a) => Agda.TypeChecking.SizedTypes.WarshallSolver.Negative (Agda.TypeChecking.SizedTypes.WarshallSolver.Graphs r f a) instance GHC.Classes.Eq f => Agda.TypeChecking.SizedTypes.WarshallSolver.SetToInfty f (Agda.TypeChecking.SizedTypes.WarshallSolver.Node r f) instance GHC.Classes.Eq f => Agda.TypeChecking.SizedTypes.WarshallSolver.SetToInfty f (Agda.TypeChecking.SizedTypes.WarshallSolver.Edge' r f a) instance (GHC.Classes.Ord r, GHC.Classes.Ord f) => Agda.TypeChecking.SizedTypes.WarshallSolver.SetToInfty f (Agda.TypeChecking.SizedTypes.WarshallSolver.ConGraph r f) instance Agda.TypeChecking.SizedTypes.Utils.Plus Agda.TypeChecking.SizedTypes.Syntax.Offset Agda.TypeChecking.SizedTypes.WarshallSolver.Weight Agda.TypeChecking.SizedTypes.WarshallSolver.Weight instance Agda.TypeChecking.SizedTypes.Utils.Plus (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' r f) Agda.TypeChecking.SizedTypes.WarshallSolver.Weight (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' r f) instance Agda.TypeChecking.SizedTypes.Utils.Plus (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' r f) Agda.TypeChecking.SizedTypes.WarshallSolver.Label (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' r f) module Agda.TypeChecking.SizedTypes.Tests type Relation a = a -> a -> Bool class AsWeightRelation b eval :: AsWeightRelation b => b -> Relation Weight prop_MeetSound :: Label -> Label -> Weight -> Weight -> Property prop_MeetComplete :: Label -> Label -> Weight -> Weight -> Property prop_ComposeSound :: Label -> Label -> Weight -> Weight -> Weight -> Property prop_ComposeComplete :: Label -> Label -> Offset -> Weight -> Property propCommutative :: Eq b => (a -> a -> b) -> a -> a -> Bool propAssociative :: Eq a => (a -> a -> a) -> a -> a -> a -> Bool propIdempotent :: Eq a => (a -> a -> a) -> a -> Bool propUnit :: Eq a => (a -> a -> a) -> a -> a -> Bool propZero :: Eq a => (a -> a -> a) -> a -> a -> Bool propDistL :: Eq b => (a -> b -> b) -> (b -> b -> b) -> a -> b -> b -> Bool propDistR :: Eq a => (a -> b -> a) -> (a -> a -> a) -> a -> a -> b -> Bool propDistributive :: Eq a => (a -> a -> a) -> (a -> a -> a) -> a -> a -> a -> Bool propSemiLattice :: Eq a => (a -> a -> a) -> a -> a -> a -> Bool propBoundedSemiLattice :: Eq a => (a -> a -> a) -> a -> a -> a -> a -> Bool propMonoid :: Eq a => (a -> a -> a) -> a -> a -> a -> a -> Bool propDioid :: Eq a => (a -> a -> a) -> a -> (a -> a -> a) -> a -> a -> a -> a -> Bool -- | Properties of Dioid class. propDioid_Gen :: Dioid a => a -> a -> a -> Bool -- | Weight instance. prop_Dioid_Weight :: Weight -> Weight -> Weight -> Bool -- | Label instance. prop_SemiLattice_Label :: Label -> Label -> Label -> Bool prop_Unit_Label :: Label -> Bool prop_BoundedSemiLattice_Label :: Label -> Label -> Label -> Bool prop_Monoid_Label :: Label -> Label -> Label -> Bool prop_DistL_Label :: Label -> Label -> Label -> Bool prop_DistR_Label :: Label -> Label -> Label -> Bool prop_Dist_Label :: Label -> Label -> Label -> Bool prop_Zero_Label :: Label -> Bool prop_Dioid_Label :: Label -> Label -> Label -> Bool -- | Runs all tests starting with "prop_" in this file. tests :: IO Bool instance Agda.TypeChecking.SizedTypes.Tests.AsWeightRelation Agda.TypeChecking.SizedTypes.Syntax.Cmp instance Agda.TypeChecking.SizedTypes.Tests.AsWeightRelation Agda.TypeChecking.SizedTypes.WarshallSolver.Label -- | A strict version of the Maybe type. -- -- Import qualified, as in import qualified Agda.Utils.Maybe.Strict -- as Strict -- -- Copyright : (c) 2006-2007 Roman Leshchinskiy (c) 2013 Simon Meier -- License : BSD-style (see the file LICENSE) -- -- Copyright : (c) 2014 Andreas Abel module Agda.Utils.Maybe.Strict toStrict :: Maybe a -> Maybe a toLazy :: Maybe a -> Maybe a -- | Analogous to listToMaybe in Data.Maybe. listToMaybe :: [a] -> Maybe a -- | Analogous to maybeToList in Data.Maybe. maybeToList :: Maybe a -> [a] -- | Analogous to catMaybes in Data.Maybe. catMaybes :: [Maybe a] -> [a] -- | Analogous to mapMaybe in Data.Maybe. mapMaybe :: (a -> Maybe b) -> [a] -> [b] -- | unionWith for collections of size <= 1. unionMaybeWith :: (a -> a -> a) -> Maybe a -> Maybe a -> Maybe a -- | Unzipping a list of length <= 1. unzipMaybe :: Maybe (a, b) -> (Maybe a, Maybe b) -- | Filtering a singleton list. -- --
--   filterMaybe p a = listToMaybe (filter p [a])
--   
filterMaybe :: (a -> Bool) -> a -> Maybe a -- | Version of mapMaybe with different argument ordering. forMaybe :: [a] -> (a -> Maybe b) -> [b] -- | Version of maybe with different argument ordering. Often, we -- want to case on a Maybe, do something interesting in the -- Just case, but only a default action in the Nothing -- case. Then, the argument ordering of caseMaybe is preferable. -- --
--   caseMaybe m err f = flip (maybe err) m f
--   
caseMaybe :: Maybe a -> b -> (a -> b) -> b -- | Monadic version of maybe. maybeM :: Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b -- | Monadic version of fromMaybe. fromMaybeM :: Monad m => m a -> m (Maybe a) -> m a -- | Monadic version of caseMaybe. That is, maybeM with a -- different argument ordering. caseMaybeM :: Monad m => m (Maybe a) -> m b -> (a -> m b) -> m b -- | caseMaybeM with flipped branches. ifJustM :: Monad m => m (Maybe a) -> (a -> m b) -> m b -> m b -- | A more telling name for forM for the Maybe collection -- type. Or: caseMaybe without the Nothing case. whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () -- | caseMaybeM without the Nothing case. whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m () instance GHC.Generics.Constructor Agda.Utils.Maybe.Strict.C1_1Maybe instance GHC.Generics.Constructor Agda.Utils.Maybe.Strict.C1_0Maybe instance GHC.Generics.Datatype Agda.Utils.Maybe.Strict.D1Maybe instance Data.Data.Data a => Data.Data.Data (Data.Strict.Maybe.Maybe a) instance GHC.Generics.Generic (Data.Strict.Maybe.Maybe a) instance Agda.Utils.Null.Null (Data.Strict.Maybe.Maybe a) instance GHC.Base.Monoid a => GHC.Base.Monoid (Data.Strict.Maybe.Maybe a) instance Data.Foldable.Foldable Data.Strict.Maybe.Maybe instance Data.Traversable.Traversable Data.Strict.Maybe.Maybe instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.Strict.Maybe.Maybe a) instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Data.Strict.Maybe.Maybe a) instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Data.Strict.Maybe.Maybe a) -- | Strict tries (based on Data.Map.Strict and -- Agda.Utils.Maybe.Strict). module Agda.Utils.Trie -- | Finite map from [k] to v. -- -- With the strict Maybe type, Trie is also strict in -- v. data Trie k v empty :: Null a => a -- | Singleton trie. singleton :: [k] -> v -> Trie k v -- | Insert. Overwrites existing value if present. -- --
--   insert = insertWith ( new old -> new)
--   
insert :: (Ord k) => [k] -> v -> Trie k v -> Trie k v -- | Insert with function merging new value with old value. insertWith :: (Ord k) => (v -> v -> v) -> [k] -> v -> Trie k v -> Trie k v -- | Left biased union. -- -- union = unionWith ( new old -> new). union :: (Ord k) => Trie k v -> Trie k v -> Trie k v -- | Pointwise union with merge function for values. unionWith :: (Ord k) => (v -> v -> v) -> Trie k v -> Trie k v -> Trie k v -- | Adjust value at key, leave subtree intact. adjust :: Ord k => [k] -> (Maybe v -> Maybe v) -> Trie k v -> Trie k v -- | Delete value at key, but leave subtree intact. delete :: Ord k => [k] -> Trie k v -> Trie k v -- | Convert to ascending list. toList :: Ord k => Trie k v -> [([k], v)] -- | Convert to ascending list. toAscList :: Ord k => Trie k v -> [([k], v)] -- | Collect all values along a given path. lookupPath :: Ord k => [k] -> Trie k v -> [v] instance GHC.Show.Show Agda.Utils.Trie.Model instance GHC.Classes.Eq Agda.Utils.Trie.Model instance GHC.Classes.Eq Agda.Utils.Trie.Val instance GHC.Classes.Ord Agda.Utils.Trie.Key instance GHC.Classes.Eq Agda.Utils.Trie.Key instance (GHC.Show.Show k, GHC.Show.Show v) => GHC.Show.Show (Agda.Utils.Trie.Trie k v) instance Agda.Utils.Null.Null (Agda.Utils.Trie.Trie k v) instance GHC.Show.Show Agda.Utils.Trie.Key instance GHC.Show.Show Agda.Utils.Trie.Val instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Utils.Trie.Key instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Utils.Trie.Val instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Utils.Trie.Model -- | Tools for benchmarking and accumulating results. Nothing Agda-specific -- in here. module Agda.Utils.Benchmark -- | Account we can bill computation time to. type Account a = [a] -- | Record when we started billing the current account. type CurrentAccount a = Maybe (Account a, CPUTime) type Timings a = Trie a CPUTime -- | Benchmark structure is a trie, mapping accounts (phases and subphases) -- to CPU time spent on their performance. data Benchmark a Benchmark :: !Bool -> !(CurrentAccount a) -> !(Timings a) -> Benchmark a -- | Are we benchmarking at all? [benchmarkOn] :: Benchmark a -> !Bool -- | What are we billing to currently? [currentAccount] :: Benchmark a -> !(CurrentAccount a) -- | The accounts and their accumulated timing bill. [timings] :: Benchmark a -> !(Timings a) -- | Initial benchmark structure (empty). -- | Semantic editor combinator. mapBenchmarkOn :: (Bool -> Bool) -> Benchmark a -> Benchmark a -- | Semantic editor combinator. mapCurrentAccount :: (CurrentAccount a -> CurrentAccount a) -> Benchmark a -> Benchmark a -- | Semantic editor combinator. mapTimings :: (Timings a -> Timings a) -> Benchmark a -> Benchmark a -- | Add to specified CPU time account. addCPUTime :: Ord a => Account a -> CPUTime -> Benchmark a -> Benchmark a -- | Print benchmark as two-column table with totals. -- | Monad with access to benchmarking data. class (Ord a, Functor m, MonadIO m) => MonadBench a m | m -> a where getsBenchmark f = f <$> getBenchmark putBenchmark b = modifyBenchmark $ const b modifyBenchmark f = do { b <- getBenchmark; putBenchmark $! f b } getBenchmark :: MonadBench a m => m (Benchmark a) getsBenchmark :: MonadBench a m => (Benchmark a -> c) -> m c putBenchmark :: MonadBench a m => Benchmark a -> m () modifyBenchmark :: MonadBench a m => (Benchmark a -> Benchmark a) -> m () -- | We need to be able to terminate benchmarking in case of an exception. finally :: MonadBench a m => m b -> m c -> m b -- | Turn benchmarking on/off. setBenchmarking :: MonadBench a m => Bool -> m () -- | Bill current account with time up to now. Switch to new account. -- Return old account (if any). switchBenchmarking :: MonadBench a m => Maybe (Account a) -> m (Maybe (Account a)) -- | Bill a computation to a specific account. Works even if the -- computation is aborted by an exception. billTo :: MonadBench a m => Account a -> m c -> m c -- | Bill a pure computation to a specific account. billPureTo :: MonadBench a m => Account a -> c -> m c instance Agda.Utils.Null.Null (Agda.Utils.Benchmark.Benchmark a) instance (GHC.Classes.Ord a, Agda.Utils.Pretty.Pretty a) => Agda.Utils.Pretty.Pretty (Agda.Utils.Benchmark.Benchmark a) instance Agda.Utils.Benchmark.MonadBench a m => Agda.Utils.Benchmark.MonadBench a (Control.Monad.Trans.Reader.ReaderT r m) -- | Agda-specific benchmarking structure. module Agda.Benchmarking -- | Phases to allocate CPU time to. data Phase -- | Happy parsing and operator parsing. Parsing :: Phase -- | Import chasing. Import :: Phase -- | Reading interface files. Deserialization :: Phase -- | Scope checking and translation to abstract syntax. Scoping :: Phase -- | Type checking and translation to internal syntax. Typing :: Phase -- | Termination checking. Termination :: Phase -- | Positivity checking and polarity computation. Positivity :: Phase -- | Injectivity checking. Injectivity :: Phase -- | Checking for projection likeness. ProjectionLikeness :: Phase -- | Coverage checking and compilation to case trees. Coverage :: Phase -- | Generating highlighting info. Highlighting :: Phase -- | Writing interface files. Serialization :: Phase -- | Subphase for Termination. Graph :: Phase -- | Subphase for Termination. RecCheck :: Phase -- | Subphase for Termination. Reduce :: Phase -- | Subphase for Termination. Level :: Phase -- | Subphase for Termination. Compare :: Phase -- | Subphase for Termination. With :: Phase -- | Subphase for Import. ModuleName :: Phase -- | Subphase for Serialize. Sort :: Phase -- | Subphase for Serialize. BinaryEncode :: Phase -- | Subphase for Serialize. Compress :: Phase -- | Subphase for Parsing. Operators :: Phase -- | Subphase for Typing: free variable computation. Free :: Phase -- | Subphase for Typing: occurs check for solving metas. OccursCheck :: Phase -- | Pretty printing names. InverseScopeLookup :: Phase type Benchmark = Benchmark Phase type Account = Account Phase -- | Global variable to store benchmark statistics. benchmarks :: IORef Benchmark -- | Benchmark an IO computation and bill it to the given account. billToIO :: Account -> IO a -> IO a -- | Benchmark a pure computation and bill it to the given account. billToPure :: Account -> a -> a instance GHC.Enum.Bounded Agda.Benchmarking.Phase instance GHC.Enum.Enum Agda.Benchmarking.Phase instance GHC.Show.Show Agda.Benchmarking.Phase instance GHC.Classes.Ord Agda.Benchmarking.Phase instance GHC.Classes.Eq Agda.Benchmarking.Phase instance Agda.Utils.Pretty.Pretty Agda.Benchmarking.Phase instance Agda.Utils.Benchmark.MonadBench Agda.Benchmarking.Phase GHC.Types.IO module Agda.Interaction.Options data CommandLineOptions Options :: String -> Maybe FilePath -> IncludeDirs -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Maybe FilePath -> Bool -> Bool -> Bool -> Maybe FilePath -> FilePath -> FilePath -> Maybe FilePath -> Bool -> Bool -> [String] -> PragmaOptions -> [String] -> Bool -> CommandLineOptions [optProgramName] :: CommandLineOptions -> String [optInputFile] :: CommandLineOptions -> Maybe FilePath [optIncludeDirs] :: CommandLineOptions -> IncludeDirs [optShowVersion] :: CommandLineOptions -> Bool [optShowHelp] :: CommandLineOptions -> Bool [optInteractive] :: CommandLineOptions -> Bool [optRunTests] :: CommandLineOptions -> Bool [optGHCiInteraction] :: CommandLineOptions -> Bool [optCompile] :: CommandLineOptions -> Bool [optCompileNoMain] :: CommandLineOptions -> Bool [optEpicCompile] :: CommandLineOptions -> Bool [optJSCompile] :: CommandLineOptions -> Bool -- | In the absence of a path the project root is used. [optCompileDir] :: CommandLineOptions -> Maybe FilePath [optGenerateVimFile] :: CommandLineOptions -> Bool [optGenerateLaTeX] :: CommandLineOptions -> Bool [optGenerateHTML] :: CommandLineOptions -> Bool [optDependencyGraph] :: CommandLineOptions -> Maybe FilePath [optLaTeXDir] :: CommandLineOptions -> FilePath [optHTMLDir] :: CommandLineOptions -> FilePath [optCSSFile] :: CommandLineOptions -> Maybe FilePath [optIgnoreInterfaces] :: CommandLineOptions -> Bool [optForcing] :: CommandLineOptions -> Bool [optGhcFlags] :: CommandLineOptions -> [String] [optPragmaOptions] :: CommandLineOptions -> PragmaOptions [optEpicFlags] :: CommandLineOptions -> [String] [optSafe] :: CommandLineOptions -> Bool -- | Options which can be set in a pragma. data PragmaOptions PragmaOptions :: Bool -> Bool -> Verbosity -> Bool -> Bool -> Bool -> Bool -> CutOff -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> PragmaOptions [optShowImplicit] :: PragmaOptions -> Bool [optShowIrrelevant] :: PragmaOptions -> Bool [optVerbose] :: PragmaOptions -> Verbosity [optProofIrrelevance] :: PragmaOptions -> Bool [optAllowUnsolved] :: PragmaOptions -> Bool [optDisablePositivity] :: PragmaOptions -> Bool [optTerminationCheck] :: PragmaOptions -> Bool -- | Cut off structural order comparison at some depth in termination -- checker? [optTerminationDepth] :: PragmaOptions -> CutOff [optCompletenessCheck] :: PragmaOptions -> Bool [optUniverseCheck] :: PragmaOptions -> Bool [optSizedTypes] :: PragmaOptions -> Bool [optInjectiveTypeConstructors] :: PragmaOptions -> Bool [optGuardingTypeConstructors] :: PragmaOptions -> Bool [optUniversePolymorphism] :: PragmaOptions -> Bool [optIrrelevantProjections] :: PragmaOptions -> Bool -- | irrelevant levels, irrelevant data matching [optExperimentalIrrelevance] :: PragmaOptions -> Bool [optWithoutK] :: PragmaOptions -> Bool -- | Allow definitions by copattern matching? [optCopatterns] :: PragmaOptions -> Bool -- | Is pattern matching allowed in the current file? [optPatternMatching] :: PragmaOptions -> Bool -- | Can rewrite rules be added and used? [optRewriting] :: PragmaOptions -> Bool -- | The options from an OPTIONS pragma. -- -- In the future it might be nice to switch to a more structured -- representation. Note that, currently, there is not a one-to-one -- correspondence between list elements and options. type OptionsPragma = [String] -- | f :: Flag opts is an action on the option record that results -- from parsing an option. f opts produces either an error -- message or an updated options record type Flag opts = opts -> Either String opts type Verbosity = Trie String Int type IncludeDirs = Either [FilePath] [AbsolutePath] 'Left' is used temporarily, before the paths have been made absolute. An empty 'Left' list is interpreted as @["."]@ (see 'Agda.TypeChecking.Monad.Options.makeIncludeDirsAbsolute'). -- | Checks that the given options are consistent. checkOpts :: Flag CommandLineOptions -- | Parse the standard options. parseStandardOptions :: [String] -> Either String CommandLineOptions -- | Parse options from an options pragma. parsePragmaOptions :: [String] -> CommandLineOptions -> Either String PragmaOptions -- | Parse options for a plugin. parsePluginOptions :: [String] -> [OptDescr (Flag opts)] -> Flag opts defaultOptions :: CommandLineOptions defaultInteractionOptions :: PragmaOptions defaultVerbosity :: Verbosity -- | The default termination depth. defaultCutOff :: CutOff -- | Used for printing usage info. standardOptions_ :: [OptDescr ()] -- | Check for unsafe pramas. Gives a list of used unsafe flags. unsafePragmaOptions :: PragmaOptions -> [String] -- | This should probably go somewhere else. isLiterate :: FilePath -> Bool -- | Map a function over the long options. Also removes the short options. -- Will be used to add the plugin name to the plugin options. mapFlag :: (String -> String) -> OptDescr a -> OptDescr a -- | The usage info message. The argument is the program name (probably -- agda). usage :: [OptDescr ()] -> [(String, String, [String], [OptDescr ()])] -> String -> String tests :: IO Bool -- | Returns the absolute default lib dir. This directory is used to store -- the Primitive.agda file. defaultLibDir :: IO FilePath inputFlag :: FilePath -> Flag CommandLineOptions standardOptions :: [OptDescr (Flag CommandLineOptions)] -- | Simple interface for System.Console.GetOpt Could be moved to -- Agda.Utils.Options (does not exist yet) getOptSimple :: [String] -> [OptDescr (Flag opts)] -> (String -> Flag opts) -> Flag opts instance GHC.Show.Show Agda.Interaction.Options.CommandLineOptions instance GHC.Show.Show Agda.Interaction.Options.PragmaOptions -- | Sparse matrices. -- -- We assume the matrices to be very sparse, so we just implement them as -- sorted association lists. -- -- Most operations are linear in the number of non-zero elements. -- -- An exception is transposition, which needs to sort the association -- list again; it has the complexity of sorting: n log n where -- n is the number of non-zero elements. -- -- Another exception is matrix multiplication, of course. module Agda.Termination.SparseMatrix -- | Type of matrices, parameterised on the type of values. -- -- Sparse matrices are implemented as an ordered association list, -- mapping coordinates to values. data Matrix i b -- | Matrix indices are lexicographically sorted with no duplicates. All -- indices must be within bounds. matrixInvariant :: (Num i, Ix i, HasZero b) => Matrix i b -> Bool -- | Size of a matrix. data Size i Size :: i -> i -> Size i -- | Number of rows, >= 0. [rows] :: Size i -> i -- | Number of columns, >= 0. [cols] :: Size i -> i -- | Size invariant: dimensions are non-negative. sizeInvariant :: (Ord i, Num i) => Size i -> Bool -- | Type of matrix indices (row, column). data MIx i MIx :: i -> i -> MIx i -- | Row index, 1 <= row <= rows. [row] :: MIx i -> i -- | Column index 1 <= col <= cols. [col] :: MIx i -> i -- | Indices must be positive, >= 1. mIxInvariant :: (Ord i, Num i) => MIx i -> Bool -- | fromLists sz rs constructs a matrix from a list of -- lists of values (a list of rows). O(size) where size = -- rows × cols. -- -- Precondition: length rs == rows sz and -- all ((cols sz ==) . length) rs. fromLists :: (Ord i, Num i, Enum i, HasZero b) => Size i -> [[b]] -> Matrix i b -- | Constructs a matrix from a list of (index, value)-pairs. -- O(n) where n is size of the list. -- -- Precondition: indices are unique. fromIndexList :: (Ord i, HasZero b) => Size i -> [(MIx i, b)] -> Matrix i b -- | Converts a matrix to a list of row lists. O(size) where -- size = rows × cols. toLists :: (Integral i, HasZero b) => Matrix i b -> [[b]] -- | Generates a matrix of the given size. matrix :: (Arbitrary i, Integral i, Arbitrary b, HasZero b) => Size i -> Gen (Matrix i b) -- | Generates a matrix of the given size, using the given generator to -- generate the rows. matrixUsingRowGen :: (Arbitrary i, Integral i, Arbitrary b, HasZero b) => Size i -> (i -> Gen [b]) -> Gen (Matrix i b) -- | Dimensions of the matrix. size :: Matrix i b -> Size i -- | True iff the matrix is square. square :: Ix i => Matrix i b -> Bool -- | Returns True iff the matrix is empty. isEmpty :: (Num i, Ix i) => Matrix i b -> Bool -- | Returns 'Just b' iff it is a 1x1 matrix with just one entry -- b. O(1). isSingleton :: (Eq i, Num i, HasZero b) => Matrix i b -> Maybe b -- | General pointwise combination function for sparse matrices. O(n1 + -- n2). zipMatrices :: (Ord i) => (a -> c) -> (b -> c) -> (a -> b -> c) -> (c -> Bool) -> Matrix i a -> Matrix i b -> Matrix i c -- | add (+) m1 m2 adds m1 and m2, using -- (+) to add values. O(n1 + n2). -- -- Returns a matrix of size supSize m1 m2. add :: (Ord i, HasZero a) => (a -> a -> a) -> Matrix i a -> Matrix i a -> Matrix i a -- | intersectWith f m1 m2 build the pointwise conjunction -- m1 and m2. Uses f to combine non-zero -- values. O(n1 + n2). -- -- Returns a matrix of size infSize m1 m2. intersectWith :: (Ord i) => (a -> a -> a) -> Matrix i a -> Matrix i a -> Matrix i a -- | mul semiring m1 m2 multiplies matrices m1 and -- m2. Uses the operations of the semiring semiring to -- perform the multiplication. -- -- O(n1 + n2 log n2 + Σ(i <= r1) Σ(j <= c2) d(i,j)) where -- r1 is the number of non-empty rows in m1 and -- c2 is the number of non-empty columns in m2 and -- d(i,j) is the bigger one of the following two quantifies: the -- length of sparse row i in m1 and the length of -- sparse column j in m2. -- -- Given dimensions m1 : r1 × c1 and m2 : r2 × c2, a -- matrix of size r1 × c2 is returned. It is not necessary that -- c1 == r2, the matrices are implicitly patched with zeros to -- match up for multiplication. For sparse matrices, this patching is a -- no-op. mul :: (Enum i, Num i, Ix i, Eq a) => Semiring a -> Matrix i a -> Matrix i a -> Matrix i a transpose :: Transpose a => a -> a -- | diagonal m extracts the diagonal of m. -- -- For non-square matrices, the length of the diagonal is the minimum of -- the dimensions of the matrix. class Diagonal m e | m -> e diagonal :: Diagonal m e => m -> [e] -- | addRow x m adds a new row to m, after the -- rows already existing in the matrix. All elements in the new row get -- set to x. addRow :: (Num i, HasZero b) => b -> Matrix i b -> Matrix i b -- | addColumn x m adds a new column to m, after -- the columns already existing in the matrix. All elements in the new -- column get set to x. addColumn :: (Num i, HasZero b) => b -> Matrix i b -> Matrix i b tests :: IO Bool instance Data.Traversable.Traversable (Agda.Termination.SparseMatrix.Matrix i) instance Data.Foldable.Foldable (Agda.Termination.SparseMatrix.Matrix i) instance GHC.Base.Functor (Agda.Termination.SparseMatrix.Matrix i) instance (GHC.Classes.Ord i, GHC.Classes.Ord b) => GHC.Classes.Ord (Agda.Termination.SparseMatrix.Matrix i b) instance (GHC.Classes.Eq i, GHC.Classes.Eq b) => GHC.Classes.Eq (Agda.Termination.SparseMatrix.Matrix i b) instance GHC.Arr.Ix i => GHC.Arr.Ix (Agda.Termination.SparseMatrix.MIx i) instance GHC.Show.Show i => GHC.Show.Show (Agda.Termination.SparseMatrix.MIx i) instance GHC.Classes.Ord i => GHC.Classes.Ord (Agda.Termination.SparseMatrix.MIx i) instance GHC.Classes.Eq i => GHC.Classes.Eq (Agda.Termination.SparseMatrix.MIx i) instance GHC.Show.Show i => GHC.Show.Show (Agda.Termination.SparseMatrix.Size i) instance GHC.Classes.Ord i => GHC.Classes.Ord (Agda.Termination.SparseMatrix.Size i) instance GHC.Classes.Eq i => GHC.Classes.Eq (Agda.Termination.SparseMatrix.Size i) instance (GHC.Real.Integral i, Agda.Termination.Semiring.HasZero b) => Agda.Termination.SparseMatrix.Diagonal (Agda.Termination.SparseMatrix.Matrix i b) b instance Agda.Termination.SparseMatrix.Transpose (Agda.Termination.SparseMatrix.Size i) instance Agda.Termination.SparseMatrix.Transpose (Agda.Termination.SparseMatrix.MIx i) instance GHC.Classes.Ord i => Agda.Termination.SparseMatrix.Transpose (Agda.Termination.SparseMatrix.Matrix i b) instance (GHC.Classes.Ord i, Agda.Utils.PartialOrd.PartialOrd a) => Agda.Utils.PartialOrd.PartialOrd (Agda.Termination.SparseMatrix.Matrix i a) instance (GHC.Real.Integral i, Agda.Termination.Semiring.HasZero b, GHC.Show.Show i, GHC.Show.Show b) => GHC.Show.Show (Agda.Termination.SparseMatrix.Matrix i b) instance (GHC.Real.Integral i, Agda.Termination.Semiring.HasZero b, Agda.Utils.Pretty.Pretty b) => Agda.Utils.Pretty.Pretty (Agda.Termination.SparseMatrix.Matrix i b) instance (Test.QuickCheck.Arbitrary.Arbitrary i, GHC.Real.Integral i) => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Termination.SparseMatrix.Size i) instance Test.QuickCheck.Arbitrary.CoArbitrary i => Test.QuickCheck.Arbitrary.CoArbitrary (Agda.Termination.SparseMatrix.Size i) instance (Test.QuickCheck.Arbitrary.Arbitrary i, GHC.Real.Integral i) => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Termination.SparseMatrix.MIx i) instance Test.QuickCheck.Arbitrary.CoArbitrary i => Test.QuickCheck.Arbitrary.CoArbitrary (Agda.Termination.SparseMatrix.MIx i) instance (Test.QuickCheck.Arbitrary.Arbitrary i, GHC.Num.Num i, GHC.Real.Integral i, Test.QuickCheck.Arbitrary.Arbitrary b, Agda.Termination.Semiring.HasZero b) => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Termination.SparseMatrix.Matrix i b) instance (GHC.Show.Show i, GHC.Classes.Ord i, GHC.Real.Integral i, GHC.Enum.Enum i, GHC.Arr.Ix i, Test.QuickCheck.Arbitrary.CoArbitrary b, Agda.Termination.Semiring.HasZero b) => Test.QuickCheck.Arbitrary.CoArbitrary (Agda.Termination.SparseMatrix.Matrix i b) -- | An Abstract domain of relative sizes, i.e., differences between size -- of formal function parameter and function argument in recursive call; -- used in the termination checker. module Agda.Termination.Order -- | In the paper referred to above, there is an order R with -- Unknown <= Le <= -- Lt. -- -- This is generalized to Unknown <= 'Decr k' -- where Decr 1 replaces Lt and Decr 0 -- replaces Le. A negative decrease means an increase. The -- generalization allows the termination checker to record an increase by -- 1 which can be compensated by a following decrease by 2 which results -- in an overall decrease. -- -- However, the termination checker of the paper itself terminates -- because there are only finitely many different call-matrices. To -- maintain termination of the terminator we set a cutoff point -- which determines how high the termination checker can count. This -- value should be set by a global or file-wise option. -- -- See Call for more information. -- -- TODO: document orders which are call-matrices themselves. data Order -- | Matrix-shaped order, currently UNUSED. Mat :: {-# UNPACK #-} !(Matrix Int Order) -> Order -- | Smart constructor for Decr k :: Order which cuts off too big -- values. -- -- Possible values for k: - ?cutoff <= k -- <= ?cutoff + 1. decr :: (?cutoff :: CutOff) => Int -> Order -- | Raw increase which does not cut off. increase :: Int -> Order -> Order -- | Raw decrease which does not cut off. decrease :: Int -> Order -> Order -- | Multiplication of Orders. (Corresponds to sequential -- composition.) (.*.) :: (?cutoff :: CutOff) => Order -> Order -> Order -- | The supremum of a (possibly empty) list of Orders. More -- information (i.e., more decrease) is bigger. Unknown is no -- information, thus, smallest. supremum :: (?cutoff :: CutOff) => [Order] -> Order -- | The infimum of a (non empty) list of Orders. Unknown is -- the least element, thus, dominant. infimum :: (?cutoff :: CutOff) => [Order] -> Order orderSemiring :: (?cutoff :: CutOff) => Semiring Order -- | le, lt, decreasing, unknown: for -- backwards compatibility, and for external use. le :: Order lt :: Order unknown :: Order -- | Smart constructor for matrix shaped orders, avoiding empty and -- singleton matrices. orderMat :: Matrix Int Order -> Order collapseO :: (?cutoff :: CutOff) => Order -> Order nonIncreasing :: Order -> Bool decreasing :: Order -> Bool -- | Matrix-shaped order is decreasing if any diagonal element is -- decreasing. isDecr :: Order -> Bool -- | A partial order, aimed at deciding whether a call graph gets worse -- during the completion. class NotWorse a notWorse :: NotWorse a => a -> a -> Bool tests :: IO Bool instance GHC.Classes.Ord Agda.Termination.Order.Order instance GHC.Classes.Eq Agda.Termination.Order.Order instance GHC.Show.Show Agda.Termination.Order.Order instance Agda.Termination.Semiring.HasZero Agda.Termination.Order.Order instance Agda.Utils.PartialOrd.PartialOrd Agda.Termination.Order.Order instance Agda.Termination.Order.NotWorse Agda.Termination.Order.Order instance GHC.Classes.Ord i => Agda.Termination.Order.NotWorse (Agda.Termination.SparseMatrix.Matrix i Agda.Termination.Order.Order) instance Agda.Utils.Pretty.Pretty Agda.Termination.Order.Order instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Termination.Order.Order instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Termination.Order.Order module Agda.Termination.CallMatrix -- | Call matrix indices = function argument indices. -- -- Machine integer Int is sufficient, since we cannot index more -- arguments than we have addresses on our machine. type ArgumentIndex = Int -- | Call matrices. -- -- A call matrix for a call f --> g has dimensions ar(g) -- × ar(f). -- -- Each column corresponds to one formal argument of caller f. -- Each row corresponds to one argument in the call to g. -- -- In the presence of dot patterns, a call argument can be related to -- several different formal arguments of f. -- -- See e.g. testsucceedDotPatternTermination.agda: -- --
--   data D : Nat -> Set where
--     cz : D zero
--     c1 : forall n -> D n -> D (suc n)
--     c2 : forall n -> D n -> D n
--   
--   f : forall n -> D n -> Nat
--   f .zero    cz        = zero
--   f .(suc n) (c1  n d) = f n (c2 n d)
--   f n        (c2 .n d) = f n d
--   
--   
-- -- Call matrices (without guardedness) are -- --
--   -1 -1   n < suc n  and       n <  c1 n d
--    ?  =                   c2 n d <= c1 n d
--   
--    = -1   n <= n     and  n < c2 n d
--    ? -1                   d < c2 n d
--   
--   
-- -- Here is a part of the original documentation for call matrices (kept -- for historical reasons): -- -- This datatype encodes information about a single recursive function -- application. The columns of the call matrix stand for source -- function arguments (patterns). The rows of the matrix stand for -- target function arguments. Element (i, j) in the -- matrix should be computed as follows: -- -- newtype CallMatrix' a CallMatrix :: Matrix ArgumentIndex a -> CallMatrix' a [mat] :: CallMatrix' a -> Matrix ArgumentIndex a type CallMatrix = CallMatrix' Order -- | Call matrix multiplication and call combination. class CallComb a (>*<) :: (CallComb a, ?cutoff :: CutOff) => a -> a -> a -- | Call matrix multiplication. -- -- f --(m1)--> g --(m2)--> h is combined to f --(m2 -- mul m1)--> h -- -- Note the reversed order of multiplication: The matrix c1 of -- the second call g-->h in the sequence -- f-->g-->h is multiplied with the matrix c2 of -- the first call. -- -- Preconditions: m1 has dimensions ar(g) × ar(f). -- m2 has dimensions ar(h) × ar(g). -- -- Postcondition: m1 >*< m2 has dimensions ar(h) × -- ar(f). -- | Call matrix augmented with path information. data CallMatrixAug cinfo CallMatrixAug :: CallMatrix -> cinfo -> CallMatrixAug cinfo -- | The matrix of the (composed call). [augCallMatrix] :: CallMatrixAug cinfo -> CallMatrix -- | Meta info, like call path. [augCallInfo] :: CallMatrixAug cinfo -> cinfo -- | Augmented call matrix multiplication. -- | Non-augmented call matrix. noAug :: Monoid cinfo => CallMatrix -> CallMatrixAug cinfo -- | Sets of incomparable call matrices augmented with path information. -- Use overloaded null, empty, singleton, -- mappend. newtype CMSet cinfo CMSet :: Favorites (CallMatrixAug cinfo) -> CMSet cinfo [cmSet] :: CMSet cinfo -> Favorites (CallMatrixAug cinfo) -- | Call matrix set product is the Cartesian product. -- | Insert into a call matrix set. insert :: CallMatrixAug cinfo -> CMSet cinfo -> CMSet cinfo -- | Union two call matrix sets. union :: CMSet cinfo -> CMSet cinfo -> CMSet cinfo -- | Convert into a list of augmented call matrices. toList :: CMSet cinfo -> [CallMatrixAug cinfo] -- | Generates a call matrix of the given size. callMatrix :: Size ArgumentIndex -> Gen CallMatrix tests :: IO Bool instance Agda.Utils.Singleton.Singleton (Agda.Termination.CallMatrix.CallMatrixAug cinfo) (Agda.Termination.CallMatrix.CMSet cinfo) instance Agda.Utils.Null.Null (Agda.Termination.CallMatrix.CMSet cinfo) instance GHC.Base.Monoid (Agda.Termination.CallMatrix.CMSet cinfo) instance Test.QuickCheck.Arbitrary.CoArbitrary cinfo => Test.QuickCheck.Arbitrary.CoArbitrary (Agda.Termination.CallMatrix.CMSet cinfo) instance Test.QuickCheck.Arbitrary.Arbitrary cinfo => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Termination.CallMatrix.CMSet cinfo) instance GHC.Show.Show cinfo => GHC.Show.Show (Agda.Termination.CallMatrix.CMSet cinfo) instance GHC.Show.Show cinfo => GHC.Show.Show (Agda.Termination.CallMatrix.CallMatrixAug cinfo) instance GHC.Classes.Eq cinfo => GHC.Classes.Eq (Agda.Termination.CallMatrix.CallMatrixAug cinfo) instance Agda.Utils.PartialOrd.PartialOrd a => Agda.Utils.PartialOrd.PartialOrd (Agda.Termination.CallMatrix.CallMatrix' a) instance (Test.QuickCheck.Arbitrary.CoArbitrary a, Agda.Termination.Semiring.HasZero a) => Test.QuickCheck.Arbitrary.CoArbitrary (Agda.Termination.CallMatrix.CallMatrix' a) instance Data.Traversable.Traversable Agda.Termination.CallMatrix.CallMatrix' instance Data.Foldable.Foldable Agda.Termination.CallMatrix.CallMatrix' instance GHC.Base.Functor Agda.Termination.CallMatrix.CallMatrix' instance (GHC.Show.Show a, Agda.Termination.Semiring.HasZero a) => GHC.Show.Show (Agda.Termination.CallMatrix.CallMatrix' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Termination.CallMatrix.CallMatrix' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Termination.CallMatrix.CallMatrix' a) instance Agda.Termination.Order.NotWorse (Agda.Termination.CallMatrix.CallMatrix' Agda.Termination.Order.Order) instance Agda.Termination.Semiring.HasZero a => Agda.Termination.SparseMatrix.Diagonal (Agda.Termination.CallMatrix.CallMatrix' a) a instance Agda.Termination.CallMatrix.CallComb Agda.Termination.CallMatrix.CallMatrix instance Agda.Termination.SparseMatrix.Diagonal (Agda.Termination.CallMatrix.CallMatrixAug cinfo) Agda.Termination.Order.Order instance Agda.Utils.PartialOrd.PartialOrd (Agda.Termination.CallMatrix.CallMatrixAug cinfo) instance Agda.Termination.Order.NotWorse (Agda.Termination.CallMatrix.CallMatrixAug cinfo) instance GHC.Base.Monoid cinfo => Agda.Termination.CallMatrix.CallComb (Agda.Termination.CallMatrix.CallMatrixAug cinfo) instance GHC.Base.Monoid cinfo => Agda.Termination.CallMatrix.CallComb (Agda.Termination.CallMatrix.CMSet cinfo) instance Agda.Utils.Pretty.Pretty Agda.Termination.CallMatrix.CallMatrix instance Agda.Utils.Pretty.Pretty cinfo => Agda.Utils.Pretty.Pretty (Agda.Termination.CallMatrix.CallMatrixAug cinfo) instance Agda.Utils.Pretty.Pretty cinfo => Agda.Utils.Pretty.Pretty (Agda.Termination.CallMatrix.CMSet cinfo) instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Termination.CallMatrix.CallMatrix instance Test.QuickCheck.Arbitrary.Arbitrary cinfo => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Termination.CallMatrix.CallMatrixAug cinfo) instance Test.QuickCheck.Arbitrary.CoArbitrary cinfo => Test.QuickCheck.Arbitrary.CoArbitrary (Agda.Termination.CallMatrix.CallMatrixAug cinfo) -- | Call graphs and related concepts, more or less as defined in "A -- Predicative Analysis of Structural Recursion" by Andreas Abel and -- Thorsten Altenkirch. module Agda.Termination.CallGraph -- | Call graph nodes. -- -- Machine integer Int is sufficient, since we cannot index more -- than we have addresses on our machine. type Node = Int -- | Calls are edges in the call graph. It can be labelled with several -- call matrices if there are several pathes from one function to -- another. type Call cinfo = Edge Node Node (CMSet cinfo) -- | Make a call with a single matrix. mkCall :: Node -> Node -> CallMatrix -> cinfo -> Call cinfo -- | Make a call with empty cinfo. mkCall' :: Monoid cinfo => Node -> Node -> CallMatrix -> Call cinfo -- | Outgoing node. source :: Edge s t e -> s -- | Incoming node. target :: Edge s t e -> t callMatrixSet :: Call cinfo -> CMSet cinfo (>*<) :: (CallComb a, ?cutoff :: CutOff) => a -> a -> a -- | A call graph is a set of calls. Every call also has some associated -- meta information, which should be Monoidal so that the meta -- information for different calls can be combined when the calls are -- combined. newtype CallGraph cinfo CallGraph :: Graph Node Node (CMSet cinfo) -> CallGraph cinfo [theCallGraph] :: CallGraph cinfo -> Graph Node Node (CMSet cinfo) -- | Returns all the nodes with incoming edges. Somewhat expensive. -- O(e). targetNodes :: CallGraph cinfo -> Set Node -- | Converts a list of calls with associated meta information to a call -- graph. fromList :: Monoid cinfo => [Call cinfo] -> CallGraph cinfo -- | Converts a call graph to a list of calls with associated meta -- information. toList :: CallGraph cinfo -> [Call cinfo] -- | Takes the union of two call graphs. union :: Monoid cinfo => CallGraph cinfo -> CallGraph cinfo -> CallGraph cinfo -- | Inserts a call into a call graph. insert :: Monoid cinfo => Node -> Node -> CallMatrix -> cinfo -> CallGraph cinfo -> CallGraph cinfo -- | Call graph comparison. A graph cs' is `worse' than -- cs if it has a new edge (call) or a call got worse, which -- means that one of its elements that was better or equal to Le -- moved a step towards Un. -- -- A call graph is complete if combining it with itself does not make it -- any worse. This is sound because of monotonicity: By combining a graph -- with itself, it can only get worse, but if it does not get worse after -- one such step, it gets never any worse. -- -- complete cs completes the call graph cs. A -- call graph is complete if it contains all indirect calls; if f -- -> g and g -> h are present in the graph, then -- f -> h should also be present. complete :: (?cutoff :: CutOff) => Monoid cinfo => CallGraph cinfo -> CallGraph cinfo completionStep :: (?cutoff :: CutOff) => Monoid cinfo => CallGraph cinfo -> CallGraph cinfo -> (CallGraph cinfo, CallGraph cinfo) tests :: IO Bool instance GHC.Show.Show cinfo => GHC.Show.Show (Agda.Termination.CallGraph.CallGraph cinfo) instance Agda.Termination.CallGraph.CombineNewOld (Agda.Termination.CallMatrix.CMSet cinfo) instance Agda.Utils.Null.Null (Agda.Termination.CallGraph.CallGraph cinfo) instance GHC.Base.Monoid cinfo => GHC.Base.Monoid (Agda.Termination.CallGraph.CallGraph cinfo) instance Agda.Utils.PartialOrd.PartialOrd a => Agda.Termination.CallGraph.CombineNewOld (Agda.Utils.Favorites.Favorites a) instance (GHC.Base.Monoid a, Agda.Termination.CallGraph.CombineNewOld a, GHC.Classes.Ord s, GHC.Classes.Ord t) => Agda.Termination.CallGraph.CombineNewOld (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Graph s t a) instance Agda.Utils.Pretty.Pretty cinfo => Agda.Utils.Pretty.Pretty (Agda.Termination.CallGraph.CallGraph cinfo) -- | Termination checker, based on "A Predicative Analysis of Structural -- Recursion" by Andreas Abel and Thorsten Altenkirch (JFP'01), and "The -- Size-Change Principle for Program Termination" by Chin Soon Lee, Neil -- Jones, and Amir Ben-Amram (POPL'01). module Agda.Termination.Termination -- | TODO: This comment seems to be partly out of date. -- -- terminates cs checks if the functions represented by -- cs terminate. The call graph cs should have one -- entry (Call) per recursive function application. -- -- Right perms is returned if the functions are -- size-change terminating. -- -- If termination can not be established, then Left -- problems is returned instead. Here problems contains an -- indication of why termination cannot be established. See -- lexOrder for further details. -- -- Note that this function assumes that all data types are strictly -- positive. -- -- The termination criterion is taken from Jones et al. In the completed -- call graph, each idempotent call-matrix from a function to itself must -- have a decreasing argument. Idempotency is wrt. matrix multiplication. -- -- This criterion is strictly more liberal than searching for a -- lexicographic order (and easier to implement, but harder to justify). terminates :: (Monoid cinfo, ?cutoff :: CutOff) => CallGraph cinfo -> Either cinfo () terminatesFilter :: (Monoid cinfo, ?cutoff :: CutOff) => (Node -> Bool) -> CallGraph cinfo -> Either cinfo () endos :: [Call cinfo] -> [CallMatrixAug cinfo] -- | A call c is idempotent if it is an endo (source == -- target) of order 1. (Endo-calls of higher orders are e.g. -- argument permutations). We can test idempotency by self-composition. -- Self-composition c >*< c should not make any -- parameter-argument relation worse. idempotent :: (?cutoff :: CutOff) => CallMatrixAug cinfo -> Bool tests :: IO Bool -- | ListT done right, see -- https://www.haskell.org/haskellwiki/ListT_done_right_alternative -- -- There is also the list-t package on hackage (Nikita Volkov) -- but it again depends on other packages we do not use yet, so we rather -- implement the few bits we need afresh. module Agda.Utils.ListT -- | Lazy monadic computation of a list of results. newtype ListT m a ListT :: m (Maybe (a, ListT m a)) -> ListT m a [runListT] :: ListT m a -> m (Maybe (a, ListT m a)) -- | The empty lazy list. nilListT :: Monad m => ListT m a -- | Consing a value to a lazy list. consListT :: Monad m => a -> ListT m a -> ListT m a -- | Singleton lazy list. sgListT :: Monad m => a -> ListT m a -- | Case distinction over lazy list. caseListT :: Monad m => ListT m a -> m b -> (a -> ListT m a -> m b) -> m b -- | Folding a lazy list, effects left-to-right. foldListT :: Monad m => (a -> m b -> m b) -> m b -> ListT m a -> m b -- | The join operation of the ListT m monad. concatListT :: Monad m => ListT m (ListT m a) -> ListT m a -- | We can `run' a computation of a ListT as it is monadic -- itself. runMListT :: Monad m => m (ListT m a) -> ListT m a -- | Monadic cons. consMListT :: Monad m => m a -> ListT m a -> ListT m a -- | Monadic singleton. sgMListT :: Monad m => m a -> ListT m a -- | Extending a monadic function to ListT. mapMListT :: (Monad m) => (a -> m b) -> ListT m a -> ListT m b -- | Alternative implementation using foldListT. mapMListT_alt :: (Monad m) => (a -> m b) -> ListT m a -> ListT m b instance GHC.Base.Functor m => GHC.Base.Functor (Agda.Utils.ListT.ListT m) instance GHC.Base.Monad m => GHC.Base.Monoid (Agda.Utils.ListT.ListT m a) instance (GHC.Base.Functor m, GHC.Base.Applicative m, GHC.Base.Monad m) => GHC.Base.Alternative (Agda.Utils.ListT.ListT m) instance (GHC.Base.Functor m, GHC.Base.Applicative m, GHC.Base.Monad m) => GHC.Base.MonadPlus (Agda.Utils.ListT.ListT m) instance (GHC.Base.Functor m, GHC.Base.Applicative m, GHC.Base.Monad m) => GHC.Base.Applicative (Agda.Utils.ListT.ListT m) instance (GHC.Base.Functor m, GHC.Base.Applicative m, GHC.Base.Monad m) => GHC.Base.Monad (Agda.Utils.ListT.ListT m) instance Control.Monad.Trans.Class.MonadTrans Agda.Utils.ListT.ListT instance (GHC.Base.Applicative m, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Agda.Utils.ListT.ListT m) instance (GHC.Base.Applicative m, Control.Monad.Reader.Class.MonadReader r m) => Control.Monad.Reader.Class.MonadReader r (Agda.Utils.ListT.ListT m) instance (GHC.Base.Applicative m, Control.Monad.State.Class.MonadState s m) => Control.Monad.State.Class.MonadState s (Agda.Utils.ListT.ListT m) -- | Quickcheck properties for ListT. module Agda.Utils.ListT.Tests -- | All tests as collected by quickCheckAll. tests :: IO Bool module Agda.Auto.NarrowingSearch type Prio = Int class Trav a blk | a -> blk trav :: (Trav a blk, Monad m) => (forall b. Trav b blk => MM b blk -> m ()) -> a -> m () data Term blk Term :: a -> Term blk -- | Result of type-checking. data Prop blk -- | Success. OK :: Prop blk -- | Definite failure. Error :: String -> Prop blk -- | Experimental. AddExtraRef :: String -> (Metavar a blk) -> (Int, RefCreateEnv blk a) -> Prop blk -- | Parallel conjunction of constraints. And :: (Maybe [Term blk]) -> (MetaEnv (PB blk)) -> (MetaEnv (PB blk)) -> Prop blk -- | Experimental, related to mcompoint. First arg is sidecondition. Sidecondition :: (MetaEnv (PB blk)) -> (MetaEnv (PB blk)) -> Prop blk -- | Forking proof on something that is not part of the term language. E.g. -- whether a term will reduce or not. Or :: Prio -> (MetaEnv (PB blk)) -> (MetaEnv (PB blk)) -> Prop blk -- | Obsolete. ConnectHandle :: (OKHandle blk) -> (MetaEnv (PB blk)) -> Prop blk data OKVal OKVal :: OKVal type OKHandle blk = MM OKVal blk type OKMeta blk = Metavar OKVal blk -- | Agsy's meta variables. -- -- a the type of the metavariable (what it can be instantiated -- with). blk the search control information (e.g. the scope of -- the meta). data Metavar a blk Metavar :: IORef (Maybe a) -> IORef Bool -> IORef [(QPB a blk, Maybe (CTree blk))] -> IORef [SubConstraints blk] -> IORef [(Int, RefCreateEnv blk a)] -> Metavar a blk -- | Maybe an instantiation (refinement). It is usually shallow, i.e., just -- one construct(or) with arguments again being metas. [mbind] :: Metavar a blk -> IORef (Maybe a) -- | Does this meta block a principal constraint (i.e., a type-checking -- constraint). [mprincipalpresent] :: Metavar a blk -> IORef Bool -- | List of observers, i.e., constraints blocked by this meta. [mobs] :: Metavar a blk -> IORef [(QPB a blk, Maybe (CTree blk))] -- | Used for experiments with independence of subproofs. [mcompoint] :: Metavar a blk -> IORef [SubConstraints blk] -- | Experimental. [mextrarefs] :: Metavar a blk -> IORef [(Int, RefCreateEnv blk a)] hequalMetavar :: Metavar a1 blk1 -> Metavar a2 bkl2 -> Bool newMeta :: IORef [SubConstraints blk] -> IO (Metavar a blk) initMeta :: IO (Metavar a blk) data CTree blk CTree :: IORef (PrioMeta blk) -> IORef (Maybe (SubConstraints blk)) -> IORef (Maybe (CTree blk)) -> IORef [OKMeta blk] -> CTree blk [ctpriometa] :: CTree blk -> IORef (PrioMeta blk) [ctsub] :: CTree blk -> IORef (Maybe (SubConstraints blk)) [ctparent] :: CTree blk -> IORef (Maybe (CTree blk)) [cthandles] :: CTree blk -> IORef [OKMeta blk] data SubConstraints blk SubConstraints :: IORef Bool -> IORef Int -> CTree blk -> CTree blk -> SubConstraints blk [scflip] :: SubConstraints blk -> IORef Bool [sccomcount] :: SubConstraints blk -> IORef Int [scsub1] :: SubConstraints blk -> CTree blk [scsub2] :: SubConstraints blk -> CTree blk newCTree :: Maybe (CTree blk) -> IO (CTree blk) newSubConstraints :: CTree blk -> IO (SubConstraints blk) data PrioMeta blk PrioMeta :: Prio -> (Metavar a blk) -> PrioMeta blk NoPrio :: Bool -> PrioMeta blk data Restore Restore :: (IORef a) -> a -> Restore type Undo = StateT [Restore] IO ureadIORef :: IORef a -> Undo a uwriteIORef :: IORef a -> a -> Undo () umodifyIORef :: IORef a -> (a -> a) -> Undo () ureadmodifyIORef :: IORef a -> (a -> a) -> Undo a runUndo :: Undo a -> IO a type RefCreateEnv blk = StateT (IORef [SubConstraints blk], Int) IO data Pair a b Pair :: a -> b -> Pair a b class Refinable a blk refinements :: Refinable a blk => blk -> [blk] -> Metavar a blk -> IO [(Int, RefCreateEnv blk a)] newPlaceholder :: RefCreateEnv blk (MM a blk) newOKHandle :: RefCreateEnv blk (OKHandle blk) dryInstantiate :: RefCreateEnv blk a -> IO a type BlkInfo blk = (Bool, Prio, Maybe blk) data MM a blk NotM :: a -> MM a blk Meta :: (Metavar a blk) -> MM a blk type MetaEnv = IO data MB a blk NotB :: a -> MB a blk Blocked :: (Metavar b blk) -> (MetaEnv (MB a blk)) -> MB a blk Failed :: String -> MB a blk data PB blk NotPB :: (Prop blk) -> PB blk PBlocked :: (Metavar b blk) -> (BlkInfo blk) -> (MetaEnv (PB blk)) -> PB blk PDoubleBlocked :: (Metavar b1 blk) -> (Metavar b2 blk) -> (MetaEnv (PB blk)) -> PB blk data QPB b blk QPBlocked :: (BlkInfo blk) -> (MetaEnv (PB blk)) -> QPB b blk QPDoubleBlocked :: (IORef Bool) -> (MetaEnv (PB blk)) -> QPB b blk mmcase :: Refinable a blk => MM a blk -> (a -> MetaEnv (MB b blk)) -> MetaEnv (MB b blk) mmmcase :: Refinable a blk => MM a blk -> MetaEnv (MB b blk) -> (a -> MetaEnv (MB b blk)) -> MetaEnv (MB b blk) mmpcase :: Refinable a blk => BlkInfo blk -> MM a blk -> (a -> MetaEnv (PB blk)) -> MetaEnv (PB blk) doubleblock :: (Refinable a blk, Refinable b blk) => MM a blk -> MM b blk -> MetaEnv (PB blk) -> MetaEnv (PB blk) mbcase :: MetaEnv (MB a blk) -> (a -> MetaEnv (MB b blk)) -> MetaEnv (MB b blk) mbpcase :: Prio -> Maybe blk -> MetaEnv (MB a blk) -> (a -> MetaEnv (PB blk)) -> MetaEnv (PB blk) mmbpcase :: MetaEnv (MB a blk) -> (forall b. Refinable b blk => MM b blk -> MetaEnv (PB blk)) -> (a -> MetaEnv (PB blk)) -> MetaEnv (PB blk) waitok :: OKHandle blk -> MetaEnv (MB b blk) -> MetaEnv (MB b blk) mbret :: a -> MetaEnv (MB a blk) mbfailed :: String -> MetaEnv (MB a blk) mpret :: Prop blk -> MetaEnv (PB blk) expandbind :: MM a blk -> MetaEnv (MM a blk) type HandleSol = IO () type SRes = Either Bool Int topSearch :: IORef Int -> IORef Int -> HandleSol -> blk -> MetaEnv (PB blk) -> Int -> Int -> IO Bool extractblkinfos :: Metavar a blk -> IO [blk] recalcs :: [(QPB a blk, Maybe (CTree blk))] -> Undo Bool seqc :: Undo Bool -> Undo Bool -> Undo Bool recalc :: (QPB a blk, Maybe (CTree blk)) -> Undo Bool reccalc :: MetaEnv (PB blk) -> Maybe (CTree blk) -> Undo Bool calc :: MetaEnv (PB blk) -> Maybe (CTree blk) -> Undo (Maybe [OKMeta blk]) choosePrioMeta :: Bool -> PrioMeta blk -> PrioMeta blk -> PrioMeta blk propagatePrio :: CTree blk -> Undo [OKMeta blk] data Choice LeftDisjunct :: Choice RightDisjunct :: Choice choose :: MM Choice blk -> Prio -> MetaEnv (PB blk) -> MetaEnv (PB blk) -> MetaEnv (PB blk) instance Agda.Auto.NarrowingSearch.Trav a blk => Agda.Auto.NarrowingSearch.Trav (Agda.Auto.NarrowingSearch.MM a blk) blk instance GHC.Classes.Eq (Agda.Auto.NarrowingSearch.Metavar a blk) instance GHC.Classes.Eq (Agda.Auto.NarrowingSearch.PrioMeta blk) instance Agda.Auto.NarrowingSearch.Refinable Agda.Auto.NarrowingSearch.Choice blk instance Agda.Auto.NarrowingSearch.Refinable Agda.Auto.NarrowingSearch.OKVal blk module Agda.Auto.Syntax -- | Unique identifiers for variable occurrences in unification. type UId o = Metavar (Exp o) (RefInfo o) data HintMode HMNormal :: HintMode HMRecCall :: HintMode data EqReasoningConsts o EqReasoningConsts :: ConstRef o -> EqReasoningConsts o [eqrcId, eqrcBegin, eqrcStep, eqrcEnd, eqrcSym, eqrcCong] :: EqReasoningConsts o -> ConstRef o data EqReasoningState EqRSNone :: EqReasoningState EqRSChain :: EqReasoningState EqRSPrf1 :: EqReasoningState EqRSPrf2 :: EqReasoningState EqRSPrf3 :: EqReasoningState -- | The concrete instance of the blk parameter in Metavar. -- I.e., the information passed to the search control. data RefInfo o RIEnv :: [(ConstRef o, HintMode)] -> Nat -> Maybe (EqReasoningConsts o) -> RefInfo o [rieHints] :: RefInfo o -> [(ConstRef o, HintMode)] -- | Nat - deffreevars (to make cost of using module parameters correspond -- to that of hints). [rieDefFreeVars] :: RefInfo o -> Nat [rieEqReasoningConsts] :: RefInfo o -> Maybe (EqReasoningConsts o) RIMainInfo :: Nat -> HNExp o -> Bool -> RefInfo o -- | Size of typing context in which meta was created. [riMainCxtLength] :: RefInfo o -> Nat -- | Head normal form of type of meta. [riMainType] :: RefInfo o -> HNExp o -- | True if iota steps performed when normalising target type (used to put -- cost when traversing a definition by construction instantiation). [riMainIota] :: RefInfo o -> Bool RIUnifInfo :: [CAction o] -> (HNExp o) -> RefInfo o RICopyInfo :: (ICExp o) -> RefInfo o RIIotaStep :: Bool -> RefInfo o RIInferredTypeUnknown :: RefInfo o RINotConstructor :: RefInfo o RIUsedVars :: [UId o] -> [Elr o] -> RefInfo o RIPickSubsvar :: RefInfo o RIEqRState :: EqReasoningState -> RefInfo o RICheckElim :: Bool -> RefInfo o RICheckProjIndex :: [ConstRef o] -> RefInfo o type MyPB o = PB (RefInfo o) type MyMB a o = MB a (RefInfo o) type Nat = Int -- | Hiding in Agda. data FMode Hidden :: FMode Instance :: FMode NotHidden :: FMode data MId Id :: String -> MId NoId :: MId stringToMyId :: String -> MId -- | Abstraction with maybe a name. -- -- Different from Agda, where there is also info whether function is -- constant. data Abs a Abs :: MId -> a -> Abs a -- | Constant signatures. data ConstDef o ConstDef :: String -> o -> MExp o -> DeclCont o -> Nat -> ConstDef o -- | For debug printing. [cdname] :: ConstDef o -> String -- | Reference to the Agda constant. [cdorigin] :: ConstDef o -> o -- | Type of constant. [cdtype] :: ConstDef o -> MExp o -- | Constant definition. [cdcont] :: ConstDef o -> DeclCont o -- | Free vars of the module where the constant is defined.. [cddeffreevars] :: ConstDef o -> Nat -- | Constant definitions. data DeclCont o Def :: Nat -> [Clause o] -> (Maybe Nat) -> (Maybe Nat) -> DeclCont o Datatype :: [ConstRef o] -> [ConstRef o] -> DeclCont o Constructor :: Nat -> DeclCont o Postulate :: DeclCont o type Clause o = ([Pat o], MExp o) data Pat o PatConApp :: (ConstRef o) -> [Pat o] -> Pat o PatVar :: String -> Pat o -- | Dot pattern. PatExp :: Pat o type ConstRef o = IORef (ConstDef o) -- | Head of application (elimination). data Elr o Var :: Nat -> Elr o Const :: (ConstRef o) -> Elr o data Sort Set :: Nat -> Sort UnknownSort :: Sort Type :: Sort -- | Agsy's internal syntax. data Exp o App :: Maybe (UId o) -> OKHandle (RefInfo o) -> Elr o -> MArgList o -> Exp o -- | Unique identifier of the head. [appUId] :: Exp o -> Maybe (UId o) -- | This application has been type-checked. [appOK] :: Exp o -> OKHandle (RefInfo o) -- | Head. [appHead] :: Exp o -> Elr o -- | Arguments. [appElims] :: Exp o -> MArgList o -- | Lambda with hiding information. Lam :: FMode -> (Abs (MExp o)) -> Exp o -- | True if possibly dependent (var not known to not occur). -- False if non-dependent. Pi :: (Maybe (UId o)) -> FMode -> Bool -> (MExp o) -> (Abs (MExp o)) -> Exp o Sort :: Sort -> Exp o -- | Absurd lambda with hiding information. AbsurdLambda :: FMode -> Exp o dontCare :: Exp o -- | "Maybe expression": Expression or reference to meta variable. type MExp o = MM (Exp o) (RefInfo o) data ArgList o -- | No more eliminations. ALNil :: ArgList o -- | Application and tail. ALCons :: FMode -> (MExp o) -> (MArgList o) -> ArgList o -- | proj pre args, projfcn idx, tail ALProj :: (MArgList o) -> (MM (ConstRef o) (RefInfo o)) -> FMode -> (MArgList o) -> ArgList o -- | Constructor parameter (missing in Agda). Agsy has monomorphic -- constructors. Inserted to cover glitch of polymorphic constructor -- applications coming from Agda ALConPar :: (MArgList o) -> ArgList o type MArgList o = MM (ArgList o) (RefInfo o) data HNExp o HNApp :: [Maybe (UId o)] -> (Elr o) -> (ICArgList o) -> HNExp o HNLam :: [Maybe (UId o)] -> FMode -> (Abs (ICExp o)) -> HNExp o HNPi :: [Maybe (UId o)] -> FMode -> Bool -> (ICExp o) -> (Abs (ICExp o)) -> HNExp o HNSort :: Sort -> HNExp o -- | Head-normal form of ICArgList. First entry is exposed. -- -- Q: Why are there no projection eliminations? data HNArgList o HNALNil :: HNArgList o HNALCons :: FMode -> (ICExp o) -> (ICArgList o) -> HNArgList o HNALConPar :: (ICArgList o) -> HNArgList o -- | Lazy concatenation of argument lists under explicit substitutions. data ICArgList o CALNil :: ICArgList o CALConcat :: (Clos (MArgList o) o) -> (ICArgList o) -> ICArgList o -- | An expression a in an explicit substitution [CAction -- a]. type ICExp o = Clos (MExp o) o data Clos a o Clos :: [CAction o] -> a -> Clos a o type CExp o = TrBr (ICExp o) o data TrBr a o TrBr :: [MExp o] -> a -> TrBr a o -- | Entry of an explicit substitution. -- -- An explicit substitution is a list of CActions. This is -- isomorphic to the usual presentation where Skip and -- Weak would be constructors of exp. substs. data CAction o -- | Instantation of variable. Sub :: (ICExp o) -> CAction o -- | For going under a binder, often called Lift. Skip :: CAction o -- | Shifting substitution (going to a larger context). Weak :: Nat -> CAction o type Ctx o = [(MId, CExp o)] type EE = IO detecteliminand :: [Clause o] -> Maybe Nat detectsemiflex :: ConstRef o -> [Clause o] -> IO Bool categorizedecl :: ConstRef o -> IO () metaliseokh :: MExp o -> IO (MExp o) expandExp :: MExp o -> IO (MExp o) addtrailingargs :: Clos (MArgList o) o -> ICArgList o -> ICArgList o closify :: MExp o -> CExp o sub :: MExp o -> CExp o -> CExp o subi :: MExp o -> ICExp o -> ICExp o weak :: Nat -> CExp o -> CExp o weaki :: Nat -> Clos a o -> Clos a o weakarglist :: Nat -> ICArgList o -> ICArgList o weakelr :: Nat -> Elr o -> Elr o -- | Substituting for a variable. doclos :: [CAction o] -> Nat -> Either Nat (ICExp o) instance GHC.Classes.Eq Agda.Auto.Syntax.FMode instance GHC.Show.Show Agda.Auto.Syntax.EqReasoningState instance GHC.Classes.Eq Agda.Auto.Syntax.EqReasoningState module Agda.Auto.SearchControl data ExpRefInfo o ExpRefInfo :: Maybe (RefInfo o) -> [RefInfo o] -> Bool -> Maybe ([UId o], [Elr o]) -> Maybe Bool -> Bool -> Maybe EqReasoningState -> ExpRefInfo o [eriMain] :: ExpRefInfo o -> Maybe (RefInfo o) [eriUnifs] :: ExpRefInfo o -> [RefInfo o] [eriInfTypeUnknown, eriIsEliminand] :: ExpRefInfo o -> Bool [eriUsedVars] :: ExpRefInfo o -> Maybe ([UId o], [Elr o]) [eriIotaStep] :: ExpRefInfo o -> Maybe Bool [eriPickSubsVar] :: ExpRefInfo o -> Bool [eriEqRState] :: ExpRefInfo o -> Maybe EqReasoningState getinfo :: [RefInfo o] -> ExpRefInfo o univar :: [CAction o] -> Nat -> Maybe Nat subsvars :: [CAction o] -> [Nat] extraref :: UId o -> [Maybe (UId o)] -> ConstRef o -> (Int, StateT (IORef [SubConstraints (RefInfo o)], Int) IO (Exp o)) costIncrease :: Int costUnificationOccurs :: Int costUnification :: Int costAppVar :: Int costAppVarUsed :: Int costAppHint :: Int costAppHintUsed :: Int costAppRecCall :: Int costAppRecCallUsed :: Int costAppConstructor :: Int costAppConstructorSingle :: Int costAppExtraRef :: Int costLam :: Int costLamUnfold :: Int costPi :: Int costSort :: Int costIotaStep :: Int costInferredTypeUnkown :: Int costAbsurdLam :: Int costEqStep :: Int costEqEnd :: Int costEqSym :: Int costEqCong :: Int prioNo :: Int prioTypeUnknown :: Int prioTypecheckArgList :: Int prioInferredTypeUnknown :: Int prioCompBeta :: Int prioCompBetaStructured :: Int prioCompareArgList :: Int prioCompIota :: Int prioCompChoice :: Int prioCompUnif :: Int prioCompCopy :: Int prioNoIota :: Int prioAbsurdLambda :: Int prioProjIndex :: Int prioTypecheck :: Bool -> Int instance Agda.Auto.NarrowingSearch.Refinable (Agda.Auto.Syntax.ArgList o) (Agda.Auto.Syntax.RefInfo o) instance Agda.Auto.NarrowingSearch.Refinable (Agda.Auto.Syntax.Exp o) (Agda.Auto.Syntax.RefInfo o) instance Agda.Auto.NarrowingSearch.Refinable (Agda.Auto.Syntax.ICExp o) (Agda.Auto.Syntax.RefInfo o) instance Agda.Auto.NarrowingSearch.Refinable (Agda.Auto.Syntax.ConstRef o) (Agda.Auto.Syntax.RefInfo o) instance Agda.Auto.NarrowingSearch.Trav a blk => Agda.Auto.NarrowingSearch.Trav [a] blk instance Agda.Auto.NarrowingSearch.Trav (Agda.Auto.Syntax.MId, Agda.Auto.Syntax.CExp o) (Agda.Auto.Syntax.RefInfo o) instance Agda.Auto.NarrowingSearch.Trav (Agda.Auto.Syntax.TrBr a o) (Agda.Auto.Syntax.RefInfo o) instance Agda.Auto.NarrowingSearch.Trav (Agda.Auto.Syntax.Exp o) (Agda.Auto.Syntax.RefInfo o) instance Agda.Auto.NarrowingSearch.Trav (Agda.Auto.Syntax.ArgList o) (Agda.Auto.Syntax.RefInfo o) module Agda.Auto.Typecheck -- | Typechecker drives the solution of metas. tcExp :: Bool -> Ctx o -> CExp o -> MExp o -> EE (MyPB o) getDatatype :: ICExp o -> EE (MyMB (Maybe (ICArgList o, [ConstRef o])) o) constructorImpossible :: ICArgList o -> ConstRef o -> EE (MyPB o) unequals :: ICArgList o -> ICArgList o -> ([(Nat, HNExp o)] -> EE (MyPB o)) -> [(Nat, HNExp o)] -> EE (MyPB o) unequal :: ICExp o -> ICExp o -> ([(Nat, HNExp o)] -> EE (MyPB o)) -> [(Nat, HNExp o)] -> EE (MyPB o) traversePi :: Int -> ICExp o -> EE (MyMB (HNExp o) o) tcargs :: Nat -> Bool -> Ctx o -> CExp o -> MArgList o -> MExp o -> Bool -> (CExp o -> MExp o -> EE (MyPB o)) -> EE (MyPB o) addend :: FMode -> MExp o -> MM (Exp o) blk -> MM (Exp o) blk copyarg :: MExp o -> Bool type HNNBlks o = [HNExp o] noblks :: HNNBlks o addblk :: HNExp o -> HNNBlks o -> HNNBlks o hnn :: ICExp o -> EE (MyMB (HNExp o) o) hnn_blks :: ICExp o -> EE (MyMB (HNExp o, HNNBlks o) o) hnn_checkstep :: ICExp o -> EE (MyMB (HNExp o, Bool) o) hnn' :: ICExp o -> ICArgList o -> EE (MyMB (HNExp o, HNNBlks o) o) hnb :: ICExp o -> ICArgList o -> EE (MyMB (HNExp o) o) data HNRes o HNDone :: (Maybe (Metavar (Exp o) (RefInfo o))) -> (HNExp o) -> HNRes o HNMeta :: (ICExp o) -> (ICArgList o) -> [Maybe (UId o)] -> HNRes o hnc :: Bool -> ICExp o -> ICArgList o -> [Maybe (UId o)] -> EE (MyMB (HNRes o) o) hnarglist :: ICArgList o -> EE (MyMB (HNArgList o) o) getNArgs :: Nat -> ICArgList o -> EE (MyMB (Maybe ([ICExp o], ICArgList o)) o) getAllArgs :: ICArgList o -> EE (MyMB [ICExp o] o) data PEval o PENo :: (ICExp o) -> PEval o PEConApp :: (ICExp o) -> (ConstRef o) -> [PEval o] -> PEval o iotastep :: Bool -> HNExp o -> EE (MyMB (Either (ICExp o, ICArgList o) (HNNBlks o)) o) noiotastep :: HNExp o -> EE (MyPB o) noiotastep_term :: ConstRef o -> MArgList o -> EE (MyPB o) data CMode o CMRigid :: (Maybe (Metavar (Exp o) (RefInfo o))) -> (HNExp o) -> CMode o CMFlex :: (MM b (RefInfo o)) -> (CMFlex o) -> CMode o data CMFlex o CMFFlex :: (ICExp o) -> (ICArgList o) -> [Maybe (UId o)] -> CMFlex o CMFSemi :: (Maybe (Metavar (Exp o) (RefInfo o))) -> (HNExp o) -> CMFlex o CMFBlocked :: (Maybe (Metavar (Exp o) (RefInfo o))) -> (HNExp o) -> CMFlex o comp' :: Bool -> CExp o -> CExp o -> EE (MyPB o) checkeliminand :: MExp o -> EE (MyPB o) maybeor :: Bool -> Int -> IO (PB (RefInfo o)) -> IO (PB (RefInfo o)) -> IO (PB (RefInfo o)) iotapossmeta :: ICExp o -> ICArgList o -> EE Bool meta_not_constructor :: ICExp o -> EE (MB Bool (RefInfo o)) calcEqRState :: EqReasoningConsts o -> MExp o -> EE (MyPB o) pickid :: MId -> MId -> MId tcSearch :: Bool -> Ctx o -> CExp o -> MExp o -> EE (MyPB o) module Agda.Auto.CaseSplit abspatvarname :: String costCaseSplitVeryHigh :: Nat costCaseSplitHigh :: Nat costCaseSplitLow :: Nat costAddVarDepth :: Nat data HI a HI :: FMode -> a -> HI a drophid :: [HI a] -> [a] type CSPat o = HI (CSPatI o) type CSCtx o = [HI (MId, MExp o)] data CSPatI o CSPatConApp :: (ConstRef o) -> [CSPat o] -> CSPatI o CSPatVar :: Nat -> CSPatI o CSPatExp :: (MExp o) -> CSPatI o CSWith :: (MExp o) -> CSPatI o CSAbsurd :: CSPatI o CSOmittedArg :: CSPatI o type Sol o = [(CSCtx o, [CSPat o], Maybe (MExp o))] caseSplitSearch :: IORef Int -> Int -> [ConstRef o] -> Maybe (EqReasoningConsts o) -> Int -> Int -> ConstRef o -> CSCtx o -> MExp o -> [CSPat o] -> IO [Sol o] caseSplitSearch' :: (Int -> CSCtx o -> MExp o -> ([Nat], Nat, [Nat]) -> IO (Maybe (MExp o))) -> Int -> Int -> ConstRef o -> CSCtx o -> MExp o -> [CSPat o] -> IO [Sol o] infertypevar :: CSCtx o -> Nat -> MExp o replace :: Nat -> Nat -> MExp o -> MExp o -> MExp o betareduce :: MExp o -> MArgList o -> MExp o concatargs :: MM (ArgList o) (RefInfo o) -> MArgList o -> MArgList o eqelr :: Elr o -> Elr o -> Bool replacep :: Nat -> Nat -> CSPatI o -> MExp o -> CSPat o -> CSPat o rm :: MM a b -> a mm :: a -> MM a b unifyexp :: MExp o -> MExp o -> Maybe [(Nat, MExp o)] lift :: Nat -> MExp o -> MExp o removevar :: CSCtx o -> MExp o -> [CSPat o] -> [(Nat, MExp o)] -> (CSCtx o, MExp o, [CSPat o]) notequal :: Nat -> Nat -> MExp o -> MExp o -> IO Bool findperm :: [MExp o] -> Maybe [Nat] freevars :: MExp o -> [Nat] applyperm :: [Nat] -> CSCtx o -> MExp o -> [CSPat o] -> (CSCtx o, MExp o, [CSPat o]) ren :: [Nat] -> Nat -> Int rename :: (Nat -> Nat) -> MExp o -> MExp o renamep :: (Nat -> Nat) -> CSPat o -> CSPat o seqctx :: CSCtx o -> CSCtx o depthofvar :: Nat -> [CSPat o] -> Nat localTerminationEnv :: [CSPat o] -> ([Nat], Nat, [Nat]) localTerminationSidecond :: ([Nat], Nat, [Nat]) -> ConstRef o -> MExp o -> EE (MyPB o) getblks :: MExp o -> IO [Nat] module Agda.Utils.HashMap -- | Like mapMaybe. mapMaybe :: (a -> Maybe b) -> HashMap k a -> HashMap k b -- | Like alter. alter :: (Eq k, Hashable k) => (Maybe a -> Maybe a) -> k -> HashMap k a -> HashMap k a -- | Position information for syntax. Crucial for giving good error -- messages. module Agda.Syntax.Position type Position = Position' SrcFile -- | Represents a point in the input. -- -- If two positions have the same srcFile and posPos -- components, then the final two components should be the same as well, -- but since this can be hard to enforce the program should not rely too -- much on the last two components; they are mainly there to improve -- error messages for the user. -- -- Note the invariant which positions have to satisfy: -- positionInvariant. data Position' a Pn :: a -> !Int32 -> !Int32 -> !Int32 -> Position' a -- | File. [srcFile] :: Position' a -> a -- | Position, counting from 1. [posPos] :: Position' a -> !Int32 -- | Line number, counting from 1. [posLine] :: Position' a -> !Int32 -- | Column number, counting from 1. [posCol] :: Position' a -> !Int32 positionInvariant :: Position' a -> Bool -- | The first position in a file: position 1, line 1, column 1. startPos :: Maybe AbsolutePath -> Position -- | Advance the position by one character. A newline character -- ('\n') moves the position to the first character in the next -- line. Any other character moves the position to the next column. movePos :: Position' a -> Char -> Position' a -- | Advance the position by a string. -- --
--   movePosByString = foldl' movePos
--   
movePosByString :: Position' a -> String -> Position' a -- | Backup the position by one character. -- -- Precondition: The character must not be '\n'. backupPos :: Position' a -> Position' a type Interval = Interval' SrcFile -- | An interval. The iEnd position is not included in the -- interval. -- -- Note the invariant which intervals have to satisfy: -- intervalInvariant. data Interval' a Interval :: !(Position' a) -> Interval' a [iStart, iEnd] :: Interval' a -> !(Position' a) intervalInvariant :: Ord a => Interval' a -> Bool -- | Extracts the interval corresponding to the given string, assuming that -- the string starts at the beginning of the given interval. -- -- Precondition: The string must not be too long for the interval. takeI :: String -> Interval' a -> Interval' a -- | Removes the interval corresponding to the given string from the given -- interval, assuming that the string starts at the beginning of the -- interval. -- -- Precondition: The string must not be too long for the interval. dropI :: String -> Interval' a -> Interval' a type Range = Range' SrcFile -- | A range is a list of intervals. The intervals should be consecutive -- and separated. -- -- Note the invariant which ranges have to satisfy: -- rangeInvariant. newtype Range' a Range :: [Interval' a] -> Range' a rangeInvariant :: Range -> Bool -- | Conflate a range to its right margin. rightMargin :: Range -> Range -- | Ranges between two unknown positions noRange :: Range' a -- | Converts two positions to a range. posToRange :: Ord a => Position' a -> Position' a -> Range' a -- | The initial position in the range, if any. rStart :: Range' a -> Maybe (Position' a) -- | The position after the final position in the range, if any. rEnd :: Range' a -> Maybe (Position' a) -- | Converts a range to an interval, if possible. rangeToInterval :: Range' a -> Maybe (Interval' a) -- | Returns the shortest continuous range containing the given one. continuous :: Range' a -> Range' a -- | Removes gaps between intervals on the same line. continuousPerLine :: Ord a => Range' a -> Range' a -- | Wrapper to indicate that range should be printed. newtype PrintRange a PrintRange :: a -> PrintRange a -- | Things that have a range are instances of this class. class HasRange t getRange :: HasRange t => t -> Range -- | If it is also possible to set the range, this is the class. -- -- Instances should satisfy getRange (setRange r x) == -- r. class HasRange t => SetRange t setRange :: SetRange t => Range -> t -> t -- | Killing the range of an object sets all range information to -- noRange. class KillRange a killRange :: KillRange a => KillRangeT a type KillRangeT a = a -> a -- | Remove ranges in keys and values of a map. killRangeMap :: (KillRange k, KillRange v) => KillRangeT (Map k v) killRange1 :: KillRange a => (a -> b) -> a -> b killRange2 :: (KillRange a, KillRange b) => (a -> b -> c) -> a -> b -> c killRange3 :: (KillRange a, KillRange b, KillRange c) => (a -> b -> c -> d) -> a -> b -> c -> d killRange4 :: (KillRange a, KillRange b, KillRange c, KillRange d) => (a -> b -> c -> d -> e) -> a -> b -> c -> d -> e killRange5 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e) => (a -> b -> c -> d -> e -> f) -> a -> b -> c -> d -> e -> f killRange6 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f) => (a -> b -> c -> d -> e -> f -> g) -> a -> b -> c -> d -> e -> f -> g killRange7 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g) => (a -> b -> c -> d -> e -> f -> g -> h) -> a -> b -> c -> d -> e -> f -> g -> h killRange8 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h) => (a -> b -> c -> d -> e -> f -> g -> h -> i) -> a -> b -> c -> d -> e -> f -> g -> h -> i killRange9 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h, KillRange i) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j killRange10 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h, KillRange i, KillRange j) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k killRange11 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h, KillRange i, KillRange j, KillRange k) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l killRange12 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h, KillRange i, KillRange j, KillRange k, KillRange l) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m killRange13 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h, KillRange i, KillRange j, KillRange k, KillRange l, KillRange m) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n) -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n killRange14 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h, KillRange i, KillRange j, KillRange k, KillRange l, KillRange m, KillRange n) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o) -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o killRange15 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h, KillRange i, KillRange j, KillRange k, KillRange l, KillRange m, KillRange n, KillRange o) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p) -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p killRange16 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h, KillRange i, KillRange j, KillRange k, KillRange l, KillRange m, KillRange n, KillRange o, KillRange p) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p -> q) -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p -> q killRange17 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h, KillRange i, KillRange j, KillRange k, KillRange l, KillRange m, KillRange n, KillRange o, KillRange p, KillRange q) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p -> q -> r) -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p -> q -> r killRange18 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h, KillRange i, KillRange j, KillRange k, KillRange l, KillRange m, KillRange n, KillRange o, KillRange p, KillRange q, KillRange r) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p -> q -> r -> s) -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p -> q -> r -> s killRange19 :: (KillRange a, KillRange b, KillRange c, KillRange d, KillRange e, KillRange f, KillRange g, KillRange h, KillRange i, KillRange j, KillRange k, KillRange l, KillRange m, KillRange n, KillRange o, KillRange p, KillRange q, KillRange r, KillRange s) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p -> q -> r -> s -> t) -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p -> q -> r -> s -> t -- | x `withRangeOf` y sets the range of x to the range -- of y. withRangeOf :: (SetRange t, HasRange u) => t -> u -> t fuseRange :: (HasRange u, HasRange t) => u -> t -> Range -- | fuseRanges r r' unions the ranges r and r'. -- -- Meaning it finds the least range r0 that covers r -- and r'. fuseRanges :: (Ord a) => Range' a -> Range' a -> Range' a -- | beginningOf r is an empty range (a single, empty interval) -- positioned at the beginning of r. If r does not have -- a beginning, then noRange is returned. beginningOf :: Range -> Range -- | beginningOfFile r is an empty range (a single, empty -- interval) at the beginning of r's starting position's file. -- If there is no such position, then an empty range is returned. beginningOfFile :: Range -> Range -- | Test suite. tests :: IO Bool instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Agda.Syntax.Position.PrintRange a) instance Agda.Syntax.Position.SetRange a => Agda.Syntax.Position.SetRange (Agda.Syntax.Position.PrintRange a) instance Agda.Syntax.Position.HasRange a => Agda.Syntax.Position.HasRange (Agda.Syntax.Position.PrintRange a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Syntax.Position.PrintRange a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Syntax.Position.PrintRange a) instance Agda.Utils.Null.Null (Agda.Syntax.Position.Range' a) instance Data.Traversable.Traversable Agda.Syntax.Position.Range' instance Data.Foldable.Foldable Agda.Syntax.Position.Range' instance GHC.Base.Functor Agda.Syntax.Position.Range' instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Syntax.Position.Range' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Syntax.Position.Range' a) instance Data.Traversable.Traversable Agda.Syntax.Position.Interval' instance Data.Foldable.Foldable Agda.Syntax.Position.Interval' instance GHC.Base.Functor Agda.Syntax.Position.Interval' instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Syntax.Position.Interval' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Syntax.Position.Interval' a) instance Data.Traversable.Traversable Agda.Syntax.Position.Position' instance Data.Foldable.Foldable Agda.Syntax.Position.Position' instance GHC.Base.Functor Agda.Syntax.Position.Position' instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Syntax.Position.Position' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Syntax.Position.Position' a) instance Agda.Syntax.Position.HasRange Agda.Syntax.Position.Interval instance Agda.Syntax.Position.HasRange Agda.Syntax.Position.Range instance Agda.Syntax.Position.HasRange a => Agda.Syntax.Position.HasRange [a] instance (Agda.Syntax.Position.HasRange a, Agda.Syntax.Position.HasRange b) => Agda.Syntax.Position.HasRange (a, b) instance (Agda.Syntax.Position.HasRange a, Agda.Syntax.Position.HasRange b, Agda.Syntax.Position.HasRange c) => Agda.Syntax.Position.HasRange (a, b, c) instance (Agda.Syntax.Position.HasRange a, Agda.Syntax.Position.HasRange b, Agda.Syntax.Position.HasRange c, Agda.Syntax.Position.HasRange d) => Agda.Syntax.Position.HasRange (a, b, c, d) instance (Agda.Syntax.Position.HasRange a, Agda.Syntax.Position.HasRange b, Agda.Syntax.Position.HasRange c, Agda.Syntax.Position.HasRange d, Agda.Syntax.Position.HasRange e) => Agda.Syntax.Position.HasRange (a, b, c, d, e) instance (Agda.Syntax.Position.HasRange a, Agda.Syntax.Position.HasRange b, Agda.Syntax.Position.HasRange c, Agda.Syntax.Position.HasRange d, Agda.Syntax.Position.HasRange e, Agda.Syntax.Position.HasRange f) => Agda.Syntax.Position.HasRange (a, b, c, d, e, f) instance (Agda.Syntax.Position.HasRange a, Agda.Syntax.Position.HasRange b, Agda.Syntax.Position.HasRange c, Agda.Syntax.Position.HasRange d, Agda.Syntax.Position.HasRange e, Agda.Syntax.Position.HasRange f, Agda.Syntax.Position.HasRange g) => Agda.Syntax.Position.HasRange (a, b, c, d, e, f, g) instance Agda.Syntax.Position.HasRange a => Agda.Syntax.Position.HasRange (GHC.Base.Maybe a) instance Agda.Syntax.Position.SetRange Agda.Syntax.Position.Range instance Agda.Syntax.Position.SetRange a => Agda.Syntax.Position.SetRange [a] instance Agda.Syntax.Position.KillRange Agda.Syntax.Position.Range instance Agda.Syntax.Position.KillRange () instance Agda.Syntax.Position.KillRange GHC.Types.Bool instance Agda.Syntax.Position.KillRange GHC.Types.Int instance Agda.Syntax.Position.KillRange GHC.Integer.Type.Integer instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange [a] instance Agda.Syntax.Position.KillRange GHC.Base.String instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Data.Map.Base.Map k a) instance (GHC.Classes.Ord a, Agda.Syntax.Position.KillRange a) => Agda.Syntax.Position.KillRange (Data.Set.Base.Set a) instance (Agda.Syntax.Position.KillRange a, Agda.Syntax.Position.KillRange b) => Agda.Syntax.Position.KillRange (a, b) instance (Agda.Syntax.Position.KillRange a, Agda.Syntax.Position.KillRange b, Agda.Syntax.Position.KillRange c) => Agda.Syntax.Position.KillRange (a, b, c) instance (Agda.Syntax.Position.KillRange a, Agda.Syntax.Position.KillRange b, Agda.Syntax.Position.KillRange c, Agda.Syntax.Position.KillRange d) => Agda.Syntax.Position.KillRange (a, b, c, d) instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (GHC.Base.Maybe a) instance (Agda.Syntax.Position.KillRange a, Agda.Syntax.Position.KillRange b) => Agda.Syntax.Position.KillRange (Data.Either.Either a b) instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Position.Position' (GHC.Base.Maybe a)) instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Position.Interval' (GHC.Base.Maybe a)) instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Position.Range' (GHC.Base.Maybe a)) instance Agda.Utils.Pretty.Pretty a => Agda.Utils.Pretty.Pretty (Agda.Syntax.Position.Position' (GHC.Base.Maybe a)) instance Agda.Utils.Pretty.Pretty a => Agda.Utils.Pretty.Pretty (Agda.Syntax.Position.Interval' (GHC.Base.Maybe a)) instance Agda.Utils.Pretty.Pretty a => Agda.Utils.Pretty.Pretty (Agda.Syntax.Position.Range' (GHC.Base.Maybe a)) instance (Agda.Utils.Pretty.Pretty a, Agda.Syntax.Position.HasRange a) => Agda.Utils.Pretty.Pretty (Agda.Syntax.Position.PrintRange a) instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Syntax.Position.Position' a) instance (Test.QuickCheck.Arbitrary.Arbitrary a, GHC.Classes.Ord a) => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Syntax.Position.Interval' a) instance (GHC.Classes.Ord a, Test.QuickCheck.Arbitrary.Arbitrary a) => Test.QuickCheck.Arbitrary.Arbitrary (Agda.Syntax.Position.Range' a) instance GHC.Show.Show (Agda.Syntax.Position.Position' GHC.Integer.Type.Integer) instance GHC.Show.Show (Agda.Syntax.Position.Interval' GHC.Integer.Type.Integer) instance GHC.Show.Show (Agda.Syntax.Position.Range' GHC.Integer.Type.Integer) -- | Some common syntactic entities are defined in this module. module Agda.Syntax.Common -- | Used to specify whether something should be delayed. data Delayed Delayed :: Delayed NotDelayed :: Delayed data Induction Inductive :: Induction CoInductive :: Induction data Hiding Hidden :: Hiding Instance :: Hiding NotHidden :: Hiding -- | Hiding is an idempotent partial monoid, with unit -- NotHidden. Instance and NotHidden are -- incompatible. -- | Decorating something with Hiding information. data WithHiding a WithHiding :: Hiding -> a -> WithHiding a -- | A lens to access the Hiding attribute in data structures. -- Minimal implementation: getHiding and one of -- setHiding or mapHiding. class LensHiding a where setHiding h = mapHiding (const h) mapHiding f a = setHiding (f $ getHiding a) a getHiding :: LensHiding a => a -> Hiding setHiding :: LensHiding a => Hiding -> a -> a mapHiding :: LensHiding a => (Hiding -> Hiding) -> a -> a -- | Monoidal composition of Hiding information in some data. mergeHiding :: LensHiding a => WithHiding a -> a -- | isHidden does not apply to Instance, only to -- Hidden. isHidden :: LensHiding a => a -> Bool -- | Visible (NotHidden) arguments are notHidden. -- (DEPRECATED, use visible.) notHidden :: LensHiding a => a -> Bool -- | NotHidden arguments are visible. visible :: LensHiding a => a -> Bool -- | Instance and Hidden arguments are notVisible. notVisible :: LensHiding a => a -> Bool hide :: LensHiding a => a -> a makeInstance :: LensHiding a => a -> a -- | An constructor argument is big if the sort of its type is bigger than -- the sort of the data type. Only parameters (and maybe forced -- arguments) are allowed to be big. List : Set -> Set nil : (A : -- Set) -> List A A is big in constructor nil -- as the sort Set1 of its type Set is bigger than the -- sort Set of the data type List. data Big Big :: Big Small :: Big -- | A function argument can be relevant or irrelevant. See -- Agda.TypeChecking.Irrelevance. data Relevance -- | The argument is (possibly) relevant at compile-time. Relevant :: Relevance -- | The argument may never flow into evaluation position. Therefore, it is -- irrelevant at run-time. It is treated relevantly during equality -- checking. NonStrict :: Relevance -- | The argument is irrelevant at compile- and runtime. Irrelevant :: Relevance -- | The argument can be skipped during equality checking because its value -- is already determined by the type. If a constructor argument is big, -- it has to be regarded absent, otherwise we get into paradoxes. Forced :: Big -> Relevance -- | The polarity checker has determined that this argument is unused in -- the definition. It can be skipped during equality checking but should -- be mined for solutions of meta-variables with relevance -- UnusedArg UnusedArg :: Relevance allRelevances :: [Relevance] -- | A lens to access the Relevance attribute in data structures. -- Minimal implementation: getRelevance and one of -- setRelevance or mapRelevance. class LensRelevance a where setRelevance h = mapRelevance (const h) mapRelevance f a = setRelevance (f $ getRelevance a) a getRelevance :: LensRelevance a => a -> Relevance setRelevance :: LensRelevance a => Relevance -> a -> a mapRelevance :: LensRelevance a => (Relevance -> Relevance) -> a -> a isRelevant :: LensRelevance a => a -> Bool isIrrelevant :: LensRelevance a => a -> Bool -- | Information ordering. Relevant `moreRelevant` UnusedArg -- `moreRelevant` Forced `moreRelevant` NonStrict `moreRelevant` -- Irrelevant moreRelevant :: Relevance -> Relevance -> Bool irrelevantOrUnused :: Relevance -> Bool -- | unusableRelevance rel == True iff we cannot use a variable of -- rel. unusableRelevance :: Relevance -> Bool -- | Relevance composition. Irrelevant is dominant, -- Relevant is neutral. composeRelevance :: Relevance -> Relevance -> Relevance -- | inverseComposeRelevance r x returns the most irrelevant -- y such that forall x, y we have x -- `moreRelevant` (r `composeRelevance` y) iff (r -- `inverseComposeRelevance` x) `moreRelevant` y (Galois -- connection). inverseComposeRelevance :: Relevance -> Relevance -> Relevance -- | For comparing Relevance ignoring Forced and -- UnusedArg. ignoreForced :: Relevance -> Relevance -- | Irrelevant function arguments may appear non-strictly in the codomain -- type. irrToNonStrict :: Relevance -> Relevance nonStrictToIrr :: Relevance -> Relevance -- | A function argument can be hidden and/or irrelevant. data ArgInfo c ArgInfo :: Hiding -> Relevance -> [c] -> ArgInfo c [argInfoHiding] :: ArgInfo c -> Hiding [argInfoRelevance] :: ArgInfo c -> Relevance [argInfoColors] :: ArgInfo c -> [c] mapArgInfoColors :: ([c] -> [c']) -> ArgInfo c -> ArgInfo c' defaultArgInfo :: ArgInfo c data Arg c e Arg :: ArgInfo c -> e -> Arg c e [argInfo] :: Arg c e -> ArgInfo c [unArg] :: Arg c e -> e mapArgInfo :: (ArgInfo c -> ArgInfo c') -> Arg c a -> Arg c' a argColors :: Arg c a -> [c] mapArgColors :: ([c] -> [c']) -> Arg c a -> Arg c' a setArgColors :: [c] -> Arg c' a -> Arg c a defaultArg :: a -> Arg c a defaultColoredArg :: ([c], a) -> Arg c a noColorArg :: Hiding -> Relevance -> a -> Arg c a -- | xs `withArgsFrom` args translates xs into a list of -- Args, using the elements in args to fill in the -- non-unArg fields. -- -- Precondition: The two lists should have equal length. withArgsFrom :: [a] -> [Arg c b] -> [Arg c a] withNamedArgsFrom :: [a] -> [NamedArg c b] -> [NamedArg c a] class Eq a => Underscore a where isUnderscore = (== underscore) underscore :: Underscore a => a isUnderscore :: Underscore a => a -> Bool -- | Similar to Arg, but we need to distinguish an irrelevance -- annotation in a function domain (the domain itself is not irrelevant!) -- from an irrelevant argument. -- -- Dom is used in Pi of internal syntax, in -- Context and Telescope. Arg is used for actual -- arguments (Var, Con, Def etc.) and in -- Abstract syntax and other situations. data Dom c e Dom :: ArgInfo c -> e -> Dom c e [domInfo] :: Dom c e -> ArgInfo c [unDom] :: Dom c e -> e mapDomInfo :: (ArgInfo c -> ArgInfo c') -> Dom c a -> Dom c' a domColors :: Dom c a -> [c] argFromDom :: Dom c a -> Arg c a domFromArg :: Arg c a -> Dom c a defaultDom :: a -> Dom c a -- | Something potentially carrying a name. data Named name a Named :: Maybe name -> a -> Named name a [nameOf] :: Named name a -> Maybe name [namedThing] :: Named name a -> a -- | Standard naming. type Named_ = Named RString unnamed :: a -> Named name a named :: name -> a -> Named name a -- | Only Hidden arguments can have names. type NamedArg c a = Arg c (Named_ a) -- | Get the content of a NamedArg. namedArg :: NamedArg c a -> a defaultNamedArg :: a -> NamedArg c a -- | The functor instance for NamedArg would be ambiguous, so we -- give it another name here. updateNamedArg :: (a -> b) -> NamedArg c a -> NamedArg c b -- | Thing with range info. data Ranged a Ranged :: Range -> a -> Ranged a [rangeOf] :: Ranged a -> Range [rangedThing] :: Ranged a -> a -- | Thing with no range info. unranged :: a -> Ranged a -- | A RawName is some sort of string. type RawName = String rawNameToString :: RawName -> String stringToRawName :: String -> RawName -- | String with range info. type RString = Ranged RawName -- | Where does the ConP of come from? data ConPOrigin -- | Expanded from an implicit pattern. ConPImplicit :: ConPOrigin -- | User wrote a constructor pattern. ConPCon :: ConPOrigin -- | User wrote a record pattern. ConPRec :: ConPOrigin -- | Functions can be defined in both infix and prefix style. See -- LHS. data IsInfix InfixDef :: IsInfix PrefixDef :: IsInfix -- | Access modifier. data Access PrivateAccess :: Access PublicAccess :: Access -- | Visible from outside, but not exported when opening the module Used -- for qualified constructors. OnlyQualified :: Access -- | Abstract or concrete data IsAbstract AbstractDef :: IsAbstract ConcreteDef :: IsAbstract -- | Is this definition eligible for instance search? data IsInstance InstanceDef :: IsInstance NotInstanceDef :: IsInstance type Nat = Int type Arity = Nat -- | The unique identifier of a name. Second argument is the top-level -- module identifier. data NameId NameId :: Integer -> Integer -> NameId -- | A meta variable identifier is just a natural number. newtype MetaId MetaId :: Nat -> MetaId [metaId] :: MetaId -> Nat -- | Show non-record version of this newtype. newtype Constr a Constr :: a -> Constr a newtype InteractionId InteractionId :: Nat -> InteractionId [interactionId] :: InteractionId -> Nat -- | Termination check? (Default = True). data TerminationCheck m -- | Run the termination checker. TerminationCheck :: TerminationCheck m -- | Skip termination checking (unsafe). NoTerminationCheck :: TerminationCheck m -- | Treat as non-terminating. NonTerminating :: TerminationCheck m -- | Treat as terminating (unsafe). Same effect as -- NoTerminationCheck. Terminating :: TerminationCheck m -- | Skip termination checking but use measure instead. TerminationMeasure :: !Range -> m -> TerminationCheck m instance GHC.Generics.Constructor Agda.Syntax.Common.C1_0NameId instance GHC.Generics.Datatype Agda.Syntax.Common.D1NameId instance GHC.Base.Functor Agda.Syntax.Common.TerminationCheck instance GHC.Classes.Eq m => GHC.Classes.Eq (Agda.Syntax.Common.TerminationCheck m) instance GHC.Show.Show m => GHC.Show.Show (Agda.Syntax.Common.TerminationCheck m) instance GHC.Enum.Enum Agda.Syntax.Common.InteractionId instance GHC.Real.Real Agda.Syntax.Common.InteractionId instance GHC.Real.Integral Agda.Syntax.Common.InteractionId instance GHC.Num.Num Agda.Syntax.Common.InteractionId instance GHC.Classes.Ord Agda.Syntax.Common.InteractionId instance GHC.Classes.Eq Agda.Syntax.Common.InteractionId instance GHC.Real.Integral Agda.Syntax.Common.MetaId instance GHC.Enum.Enum Agda.Syntax.Common.MetaId instance GHC.Real.Real Agda.Syntax.Common.MetaId instance GHC.Num.Num Agda.Syntax.Common.MetaId instance GHC.Classes.Ord Agda.Syntax.Common.MetaId instance GHC.Classes.Eq Agda.Syntax.Common.MetaId instance GHC.Generics.Generic Agda.Syntax.Common.NameId instance GHC.Classes.Ord Agda.Syntax.Common.NameId instance GHC.Classes.Eq Agda.Syntax.Common.NameId instance GHC.Classes.Ord Agda.Syntax.Common.IsInstance instance GHC.Classes.Eq Agda.Syntax.Common.IsInstance instance GHC.Show.Show Agda.Syntax.Common.IsInstance instance GHC.Classes.Ord Agda.Syntax.Common.IsAbstract instance GHC.Classes.Eq Agda.Syntax.Common.IsAbstract instance GHC.Show.Show Agda.Syntax.Common.IsAbstract instance GHC.Classes.Ord Agda.Syntax.Common.Access instance GHC.Classes.Eq Agda.Syntax.Common.Access instance GHC.Show.Show Agda.Syntax.Common.Access instance GHC.Classes.Ord Agda.Syntax.Common.IsInfix instance GHC.Classes.Eq Agda.Syntax.Common.IsInfix instance GHC.Show.Show Agda.Syntax.Common.IsInfix instance GHC.Enum.Bounded Agda.Syntax.Common.ConPOrigin instance GHC.Enum.Enum Agda.Syntax.Common.ConPOrigin instance GHC.Classes.Ord Agda.Syntax.Common.ConPOrigin instance GHC.Classes.Eq Agda.Syntax.Common.ConPOrigin instance GHC.Show.Show Agda.Syntax.Common.ConPOrigin instance Data.Traversable.Traversable Agda.Syntax.Common.Ranged instance Data.Foldable.Foldable Agda.Syntax.Common.Ranged instance GHC.Base.Functor Agda.Syntax.Common.Ranged instance Data.Traversable.Traversable (Agda.Syntax.Common.Named name) instance Data.Foldable.Foldable (Agda.Syntax.Common.Named name) instance GHC.Base.Functor (Agda.Syntax.Common.Named name) instance (GHC.Classes.Ord name, GHC.Classes.Ord a) => GHC.Classes.Ord (Agda.Syntax.Common.Named name a) instance (GHC.Classes.Eq name, GHC.Classes.Eq a) => GHC.Classes.Eq (Agda.Syntax.Common.Named name a) instance Data.Traversable.Traversable (Agda.Syntax.Common.Dom c) instance Data.Foldable.Foldable (Agda.Syntax.Common.Dom c) instance GHC.Base.Functor (Agda.Syntax.Common.Dom c) instance (GHC.Classes.Ord c, GHC.Classes.Ord e) => GHC.Classes.Ord (Agda.Syntax.Common.Dom c e) instance (GHC.Classes.Eq c, GHC.Classes.Eq e) => GHC.Classes.Eq (Agda.Syntax.Common.Dom c e) instance Data.Traversable.Traversable (Agda.Syntax.Common.Arg c) instance Data.Foldable.Foldable (Agda.Syntax.Common.Arg c) instance GHC.Base.Functor (Agda.Syntax.Common.Arg c) instance (GHC.Classes.Ord c, GHC.Classes.Ord e) => GHC.Classes.Ord (Agda.Syntax.Common.Arg c e) instance GHC.Show.Show c => GHC.Show.Show (Agda.Syntax.Common.ArgInfo c) instance Data.Traversable.Traversable Agda.Syntax.Common.ArgInfo instance Data.Foldable.Foldable Agda.Syntax.Common.ArgInfo instance GHC.Base.Functor Agda.Syntax.Common.ArgInfo instance GHC.Classes.Ord c => GHC.Classes.Ord (Agda.Syntax.Common.ArgInfo c) instance GHC.Classes.Eq c => GHC.Classes.Eq (Agda.Syntax.Common.ArgInfo c) instance GHC.Classes.Eq Agda.Syntax.Common.Relevance instance GHC.Show.Show Agda.Syntax.Common.Relevance instance GHC.Enum.Bounded Agda.Syntax.Common.Big instance GHC.Enum.Enum Agda.Syntax.Common.Big instance GHC.Classes.Eq Agda.Syntax.Common.Big instance GHC.Show.Show Agda.Syntax.Common.Big instance Data.Traversable.Traversable Agda.Syntax.Common.WithHiding instance Data.Foldable.Foldable Agda.Syntax.Common.WithHiding instance GHC.Base.Functor Agda.Syntax.Common.WithHiding instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Common.WithHiding a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Syntax.Common.WithHiding a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Syntax.Common.WithHiding a) instance GHC.Classes.Ord Agda.Syntax.Common.Hiding instance GHC.Classes.Eq Agda.Syntax.Common.Hiding instance GHC.Show.Show Agda.Syntax.Common.Hiding instance GHC.Classes.Ord Agda.Syntax.Common.Induction instance GHC.Classes.Eq Agda.Syntax.Common.Induction instance GHC.Classes.Ord Agda.Syntax.Common.Delayed instance GHC.Classes.Eq Agda.Syntax.Common.Delayed instance GHC.Show.Show Agda.Syntax.Common.Delayed instance Agda.Syntax.Position.KillRange Agda.Syntax.Common.Delayed instance GHC.Show.Show Agda.Syntax.Common.Induction instance Agda.Syntax.Position.HasRange Agda.Syntax.Common.Induction instance Agda.Syntax.Position.KillRange Agda.Syntax.Common.Induction instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Syntax.Common.Induction instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Syntax.Common.Induction instance GHC.Base.Monoid Agda.Syntax.Common.Hiding instance Agda.Syntax.Position.KillRange Agda.Syntax.Common.Hiding instance Agda.Utils.Functor.Decoration Agda.Syntax.Common.WithHiding instance GHC.Base.Applicative Agda.Syntax.Common.WithHiding instance Agda.Syntax.Position.HasRange a => Agda.Syntax.Position.HasRange (Agda.Syntax.Common.WithHiding a) instance Agda.Syntax.Position.SetRange a => Agda.Syntax.Position.SetRange (Agda.Syntax.Common.WithHiding a) instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Agda.Syntax.Common.WithHiding a) instance Agda.Syntax.Common.LensHiding Agda.Syntax.Common.Hiding instance Agda.Syntax.Common.LensHiding (Agda.Syntax.Common.WithHiding a) instance GHC.Classes.Ord Agda.Syntax.Common.Big instance Agda.Syntax.Position.KillRange Agda.Syntax.Common.Relevance instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Syntax.Common.Relevance instance GHC.Classes.Ord Agda.Syntax.Common.Relevance instance Agda.Syntax.Common.LensRelevance Agda.Syntax.Common.Relevance instance Agda.Syntax.Position.KillRange c => Agda.Syntax.Position.KillRange (Agda.Syntax.Common.ArgInfo c) instance Agda.Syntax.Common.LensHiding (Agda.Syntax.Common.ArgInfo c) instance Agda.Syntax.Common.LensRelevance (Agda.Syntax.Common.ArgInfo c) instance Agda.Utils.Functor.Decoration (Agda.Syntax.Common.Arg c) instance Agda.Syntax.Position.HasRange a => Agda.Syntax.Position.HasRange (Agda.Syntax.Common.Arg c a) instance Agda.Syntax.Position.SetRange a => Agda.Syntax.Position.SetRange (Agda.Syntax.Common.Arg c a) instance (Agda.Syntax.Position.KillRange c, Agda.Syntax.Position.KillRange a) => Agda.Syntax.Position.KillRange (Agda.Syntax.Common.Arg c a) instance (GHC.Classes.Eq a, GHC.Classes.Eq c) => GHC.Classes.Eq (Agda.Syntax.Common.Arg c a) instance (GHC.Show.Show a, GHC.Show.Show c) => GHC.Show.Show (Agda.Syntax.Common.Arg c a) instance Agda.Syntax.Common.LensHiding (Agda.Syntax.Common.Arg c e) instance Agda.Syntax.Common.LensRelevance (Agda.Syntax.Common.Arg c e) instance Agda.Syntax.Common.Underscore GHC.Base.String instance Agda.Syntax.Common.Underscore Data.ByteString.Internal.ByteString instance Agda.Syntax.Common.Underscore Text.PrettyPrint.HughesPJ.Doc instance Agda.Utils.Functor.Decoration (Agda.Syntax.Common.Dom c) instance Agda.Syntax.Position.HasRange a => Agda.Syntax.Position.HasRange (Agda.Syntax.Common.Dom c a) instance (Agda.Syntax.Position.KillRange c, Agda.Syntax.Position.KillRange a) => Agda.Syntax.Position.KillRange (Agda.Syntax.Common.Dom c a) instance (GHC.Show.Show a, GHC.Show.Show c) => GHC.Show.Show (Agda.Syntax.Common.Dom c a) instance Agda.Syntax.Common.LensHiding (Agda.Syntax.Common.Dom c e) instance Agda.Syntax.Common.LensRelevance (Agda.Syntax.Common.Dom c e) instance Agda.Utils.Functor.Decoration (Agda.Syntax.Common.Named name) instance Agda.Syntax.Position.HasRange a => Agda.Syntax.Position.HasRange (Agda.Syntax.Common.Named name a) instance Agda.Syntax.Position.SetRange a => Agda.Syntax.Position.SetRange (Agda.Syntax.Common.Named name a) instance (Agda.Syntax.Position.KillRange name, Agda.Syntax.Position.KillRange a) => Agda.Syntax.Position.KillRange (Agda.Syntax.Common.Named name a) instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Common.Named_ a) instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Common.Ranged a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Syntax.Common.Ranged a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Syntax.Common.Ranged a) instance Agda.Syntax.Position.HasRange (Agda.Syntax.Common.Ranged a) instance Agda.Syntax.Position.KillRange (Agda.Syntax.Common.Ranged a) instance Agda.Utils.Functor.Decoration Agda.Syntax.Common.Ranged instance Agda.Syntax.Position.KillRange Agda.Syntax.Common.IsAbstract instance Agda.Syntax.Position.KillRange Agda.Syntax.Common.NameId instance GHC.Show.Show Agda.Syntax.Common.NameId instance GHC.Enum.Enum Agda.Syntax.Common.NameId instance Data.Hashable.Class.Hashable Agda.Syntax.Common.NameId instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Syntax.Common.NameId instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Syntax.Common.NameId instance Agda.Utils.Pretty.Pretty Agda.Syntax.Common.MetaId instance GHC.Show.Show Agda.Syntax.Common.MetaId instance GHC.Show.Show Agda.Syntax.Common.InteractionId instance Agda.Syntax.Position.KillRange Agda.Syntax.Common.InteractionId instance Agda.Syntax.Position.KillRange m => Agda.Syntax.Position.KillRange (Agda.Syntax.Common.TerminationCheck m) module Agda.Compiler.JS.Syntax data Exp Self :: Exp Local :: LocalId -> Exp Global :: GlobalId -> Exp Undefined :: Exp String :: String -> Exp Char :: Char -> Exp Integer :: Integer -> Exp Double :: Double -> Exp Lambda :: Nat -> Exp -> Exp Object :: (Map MemberId Exp) -> Exp Apply :: Exp -> [Exp] -> Exp Lookup :: Exp -> MemberId -> Exp If :: Exp -> Exp -> Exp -> Exp BinOp :: Exp -> String -> Exp -> Exp PreOp :: String -> Exp -> Exp Const :: String -> Exp newtype LocalId LocalId :: Nat -> LocalId newtype GlobalId GlobalId :: [String] -> GlobalId newtype MemberId MemberId :: String -> MemberId data Export Export :: [MemberId] -> Exp -> Export [expName] :: Export -> [MemberId] [defn] :: Export -> Exp data Module Module :: GlobalId -> [Export] -> Module [modName] :: Module -> GlobalId [exports] :: Module -> [Export] class Uses a uses :: Uses a => a -> Set [MemberId] class Globals a globals :: Globals a => a -> Set GlobalId instance GHC.Show.Show Agda.Compiler.JS.Syntax.Module instance GHC.Show.Show Agda.Compiler.JS.Syntax.Export instance GHC.Show.Show Agda.Compiler.JS.Syntax.Exp instance GHC.Show.Show Agda.Compiler.JS.Syntax.MemberId instance GHC.Classes.Ord Agda.Compiler.JS.Syntax.MemberId instance GHC.Classes.Eq Agda.Compiler.JS.Syntax.MemberId instance GHC.Show.Show Agda.Compiler.JS.Syntax.GlobalId instance GHC.Classes.Ord Agda.Compiler.JS.Syntax.GlobalId instance GHC.Classes.Eq Agda.Compiler.JS.Syntax.GlobalId instance GHC.Show.Show Agda.Compiler.JS.Syntax.LocalId instance GHC.Classes.Ord Agda.Compiler.JS.Syntax.LocalId instance GHC.Classes.Eq Agda.Compiler.JS.Syntax.LocalId instance Agda.Compiler.JS.Syntax.Uses a => Agda.Compiler.JS.Syntax.Uses [a] instance Agda.Compiler.JS.Syntax.Uses a => Agda.Compiler.JS.Syntax.Uses (Data.Map.Base.Map k a) instance Agda.Compiler.JS.Syntax.Uses Agda.Compiler.JS.Syntax.Exp instance Agda.Compiler.JS.Syntax.Uses Agda.Compiler.JS.Syntax.Export instance Agda.Compiler.JS.Syntax.Globals a => Agda.Compiler.JS.Syntax.Globals [a] instance Agda.Compiler.JS.Syntax.Globals a => Agda.Compiler.JS.Syntax.Globals (Data.Map.Base.Map k a) instance Agda.Compiler.JS.Syntax.Globals Agda.Compiler.JS.Syntax.Exp instance Agda.Compiler.JS.Syntax.Globals Agda.Compiler.JS.Syntax.Export instance Agda.Compiler.JS.Syntax.Globals Agda.Compiler.JS.Syntax.Module module Agda.Compiler.JS.Pretty br :: Int -> String unescape :: Char -> String unescapes :: String -> String class Pretty a pretty :: Pretty a => Nat -> Int -> a -> String class Pretties a pretties :: Pretties a => Nat -> Int -> a -> [String] block :: Nat -> Int -> Exp -> String block' :: Nat -> Int -> Exp -> String modname :: GlobalId -> String exports :: Nat -> Int -> Set [MemberId] -> [Export] -> String instance (Agda.Compiler.JS.Pretty.Pretty a, Agda.Compiler.JS.Pretty.Pretty b) => Agda.Compiler.JS.Pretty.Pretty (a, b) instance Agda.Compiler.JS.Pretty.Pretty a => Agda.Compiler.JS.Pretty.Pretties [a] instance (Agda.Compiler.JS.Pretty.Pretty a, Agda.Compiler.JS.Pretty.Pretty b) => Agda.Compiler.JS.Pretty.Pretties (Data.Map.Base.Map a b) instance Agda.Compiler.JS.Pretty.Pretty Agda.Compiler.JS.Syntax.LocalId instance Agda.Compiler.JS.Pretty.Pretty Agda.Compiler.JS.Syntax.GlobalId instance Agda.Compiler.JS.Pretty.Pretty Agda.Compiler.JS.Syntax.MemberId instance Agda.Compiler.JS.Pretty.Pretty Agda.Compiler.JS.Syntax.Exp instance Agda.Compiler.JS.Pretty.Pretty Agda.Compiler.JS.Syntax.Module module Agda.Compiler.JS.Substitution map :: Nat -> (Nat -> LocalId -> Exp) -> Exp -> Exp shift :: Nat -> Exp -> Exp shiftFrom :: Nat -> Nat -> Exp -> Exp shifter :: Nat -> Nat -> LocalId -> Exp subst :: Nat -> [Exp] -> Exp -> Exp substituter :: Nat -> [Exp] -> Nat -> LocalId -> Exp map' :: Nat -> (Nat -> LocalId -> Exp) -> Exp -> Exp subst' :: Nat -> [Exp] -> Exp -> Exp apply :: Exp -> [Exp] -> Exp lookup :: Exp -> MemberId -> Exp self :: Exp -> Exp -> Exp fix :: Exp -> Exp curriedApply :: Exp -> [Exp] -> Exp curriedLambda :: Nat -> Exp -> Exp emp :: Exp union :: Exp -> Exp -> Exp vine :: [MemberId] -> Exp -> Exp object :: [([MemberId], Exp)] -> Exp module Agda.Compiler.JS.Case data Case Case :: [Patt] -> Exp -> Case [pats] :: Case -> [Patt] [body] :: Case -> Exp data Patt VarPatt :: Patt Tagged :: Tag -> [Patt] -> Patt data Tag Tag :: MemberId -> [MemberId] -> (Exp -> [Exp] -> Exp) -> Tag numVars :: [Patt] -> Nat numVars' :: Patt -> Nat lambda :: [Case] -> Exp lambda' :: Nat -> Nat -> Nat -> [Case] -> Exp pop :: Case -> Case match :: Nat -> Nat -> Nat -> [Case] -> MemberId -> Nat -> Exp refine :: MemberId -> Nat -> Case -> [Case] visit :: [Case] -> Exp -> [Exp] -> Exp tags :: [Case] -> Map MemberId Nat tag :: Case -> Map MemberId Nat instance GHC.Show.Show Agda.Compiler.JS.Case.Case instance GHC.Show.Show Agda.Compiler.JS.Case.Patt instance Agda.Compiler.JS.Pretty.Pretty Agda.Compiler.JS.Case.Case instance Agda.Compiler.JS.Pretty.Pretty Agda.Compiler.JS.Case.Patt instance GHC.Show.Show Agda.Compiler.JS.Case.Tag module Agda.Compiler.JS.Parser type Parser = ReadP Char identifier :: Parser String wordBoundary :: Parser () token :: String -> Parser () punct :: Char -> Parser () parened :: Parser a -> Parser a braced :: Parser a -> Parser a bracketed :: Parser a -> Parser a quoted :: Parser a -> Parser a stringLit :: Parser Exp stringStr :: Parser String stringChr :: Parser Char escChr :: Parser Char intLit :: Parser Exp undef :: Parser Exp localid :: (Map String Nat) -> Parser Exp globalid :: Parser Exp preop :: Parser String binop :: Parser String field :: (Map String Nat) -> Parser (MemberId, Exp) object :: (Map String Nat) -> Parser Exp function :: (Map String Nat) -> Parser Exp bracedBlock :: (Map String Nat) -> Parser Exp returnBlock :: (Map String Nat) -> Parser Exp ifBlock :: (Map String Nat) -> Parser Exp exp0 :: (Map String Nat) -> Parser Exp exp1 :: (Map String Nat) -> Parser Exp exp2 :: (Map String Nat) -> Parser Exp exp2' :: (Map String Nat) -> Exp -> Parser Exp exp3 :: (Map String Nat) -> Parser Exp exp3' :: (Map String Nat) -> Exp -> Parser Exp exp :: (Map String Nat) -> Parser Exp topLevel :: Parser Exp parse :: String -> Either Exp String -- | Construct a graph from constraints x + n y becomes x -- ---(-n)--- y x n + y becomes x ---(+n)--- y the -- default edge (= no edge) is labelled with infinity. -- -- Building the graph involves keeping track of the node names. We do -- this in a finite map, assigning consecutive numbers to nodes. module Agda.Utils.Warshall type Matrix a = Array (Int, Int) a warshall :: SemiRing a => Matrix a -> Matrix a type AdjList node edge = Map node [(node, edge)] -- | Warshall's algorithm on a graph represented as an adjacency list. warshallG :: (SemiRing edge, Ord node) => AdjList node edge -> AdjList node edge -- | Edge weight in the graph, forming a semi ring. data Weight Finite :: Int -> Weight Infinite :: Weight inc :: Weight -> Int -> Weight -- | Nodes of the graph are either - flexible variables (with identifiers -- drawn from Int), - rigid variables (also identified by -- Ints), or - constants (like 0, infinity, or anything -- between). data Node Rigid :: Rigid -> Node Flex :: FlexId -> Node data Rigid RConst :: Weight -> Rigid RVar :: RigidId -> Rigid type NodeId = Int type RigidId = Int type FlexId = Int -- | Which rigid variables a flex may be instatiated to. type Scope = RigidId -> Bool infinite :: Rigid -> Bool -- | isBelow r w r' checks, if r and r' are -- connected by w (meaning w not infinite), whether -- r + w <= r'. Precondition: not the same rigid variable. isBelow :: Rigid -> Weight -> Rigid -> Bool -- | A constraint is an edge in the graph. data Constraint NewFlex :: FlexId -> Scope -> Constraint -- | For Arc v1 k v2 at least one of v1 or v2 is -- a MetaV (Flex), the other a MetaV or a Var -- (Rigid). If k <= 0 this means suc^(-k) v1 <= -- v2 otherwise v1 <= suc^k v3. Arc :: Node -> Int -> Node -> Constraint type Constraints = [Constraint] emptyConstraints :: Constraints data Graph Graph :: Map FlexId Scope -> Map Node NodeId -> Map NodeId Node -> NodeId -> (NodeId -> NodeId -> Weight) -> Graph -- | Scope for each flexible var. [flexScope] :: Graph -> Map FlexId Scope -- | Node labels to node numbers. [nodeMap] :: Graph -> Map Node NodeId -- | Node numbers to node labels. [intMap] :: Graph -> Map NodeId Node -- | Number of nodes n. [nextNode] :: Graph -> NodeId -- | The edges (restrict to [0..n[). [graph] :: Graph -> NodeId -> NodeId -> Weight -- | The empty graph: no nodes, edges are all undefined (infinity weight). initGraph :: Graph -- | The Graph Monad, for constructing a graph iteratively. type GM = State Graph -- | Add a size meta node. addFlex :: FlexId -> Scope -> GM () -- | Lookup identifier of a node. If not present, it is added first. addNode :: Node -> GM Int -- | addEdge n1 k n2 improves the weight of egde -- n1->n2 to be at most k. Also adds nodes if not -- yet present. addEdge :: Node -> Int -> Node -> GM () addConstraint :: Constraint -> GM () buildGraph :: Constraints -> Graph mkMatrix :: Int -> (Int -> Int -> Weight) -> Matrix Weight -- | A matrix with row descriptions in b and column descriptions -- in c. data LegendMatrix a b c LegendMatrix :: Matrix a -> (Int -> b) -> (Int -> c) -> LegendMatrix a b c [matrix] :: LegendMatrix a b c -> Matrix a [rowdescr] :: LegendMatrix a b c -> Int -> b [coldescr] :: LegendMatrix a b c -> Int -> c -- | A solution assigns to each flexible variable a size expression which -- is either a constant or a v + n for a rigid variable -- v. type Solution = Map Int SizeExpr emptySolution :: Solution extendSolution :: Solution -> Int -> SizeExpr -> Solution data SizeExpr -- | e.g. x + 5 SizeVar :: RigidId -> Int -> SizeExpr -- | a number or infinity SizeConst :: Weight -> SizeExpr -- | sizeRigid r n returns the size expression corresponding to -- r + n sizeRigid :: Rigid -> Int -> SizeExpr solve :: Constraints -> Maybe Solution genGraph :: Ord node => Float -> Gen edge -> [node] -> Gen (AdjList node edge) type Distance = Weight genGraph_ :: Nat -> Gen (AdjList Nat Distance) lookupEdge :: Ord n => n -> n -> AdjList n e -> Maybe e edges :: Ord n => AdjList n e -> [(n, n, e)] -- | Check that no edges get longer when completing a graph. prop_smaller :: Nat -> Property newEdge :: Nat -> Nat -> Distance -> AdjList Nat Distance -> AdjList Nat Distance genPath :: Nat -> Nat -> Nat -> AdjList Nat Distance -> Gen (AdjList Nat Distance) -- | Check that all transitive edges are added. prop_path :: Nat -> Property mapNodes :: (Ord node, Ord node') => (node -> node') -> AdjList node edge -> AdjList node' edge -- | Check that no edges are added between components. prop_disjoint :: Nat -> Property prop_stable :: Nat -> Property tests :: IO Bool instance GHC.Classes.Ord Agda.Utils.Warshall.Node instance GHC.Classes.Eq Agda.Utils.Warshall.Node instance GHC.Show.Show Agda.Utils.Warshall.Rigid instance GHC.Classes.Ord Agda.Utils.Warshall.Rigid instance GHC.Classes.Eq Agda.Utils.Warshall.Rigid instance GHC.Classes.Eq Agda.Utils.Warshall.Weight instance GHC.Show.Show Agda.Utils.Warshall.Weight instance GHC.Classes.Ord Agda.Utils.Warshall.Weight instance Agda.Utils.SemiRing.SemiRing Agda.Utils.Warshall.Weight instance GHC.Show.Show Agda.Utils.Warshall.Node instance GHC.Show.Show Agda.Utils.Warshall.Constraint instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c) => GHC.Show.Show (Agda.Utils.Warshall.LegendMatrix a b c) instance GHC.Show.Show Agda.Utils.Warshall.SizeExpr -- | Names in the concrete syntax are just strings (or lists of strings for -- qualified names). module Agda.Syntax.Concrete.Name -- | A name is a non-empty list of alternating Ids and Holes. -- A normal name is represented by a singleton list, and operators are -- represented by a list with Holes where the arguments should go. -- For instance: [Hole,Id "+",Hole] is infix addition. -- -- Equality and ordering on Names are defined to ignore range so -- same names in different locations are equal. data Name -- | A (mixfix) identifier. Name :: !Range -> [NamePart] -> Name -- | _. NoName :: !Range -> NameId -> Name -- | Mixfix identifiers are composed of words and holes, e.g. _+_ -- or if_then_else_ or [_/_]. data NamePart -- | _ part. Hole :: NamePart -- | Identifier part. Id :: RawName -> NamePart -- | Define equality on Name to ignore range so same names in -- different locations are equal. -- -- Is there a reason not to do this? -Jeff -- -- No. But there are tons of reasons to do it. For instance, when using -- names as keys in maps you really don't want to have to get the range -- right to be able to do a lookup. -Ulf -- | QName is a list of namespaces and the name of the constant. -- For the moment assumes namespaces are just Names and not -- explicitly applied modules. Also assumes namespaces are generative by -- just using derived equality. We will have to define an equality -- instance to non-generative namespaces (as well as having some sort of -- lookup table for namespace names). data QName -- | A.rest. Qual :: Name -> QName -> QName -- | x. QName :: Name -> QName -- | Top-level module names. Used in connection with the file system. -- -- Invariant: The list must not be empty. newtype TopLevelModuleName TopLevelModuleName :: [String] -> TopLevelModuleName [moduleNameParts] :: TopLevelModuleName -> [String] nameToRawName :: Name -> RawName nameParts :: Name -> [NamePart] nameStringParts :: Name -> [RawName] -- | Parse a string to parts of a concrete name. stringNameParts :: String -> [NamePart] -- | Is the name an operator? isOperator :: Name -> Bool isHole :: NamePart -> Bool isPrefix :: Name -> Bool isPostfix :: Name -> Bool isInfix :: Name -> Bool isNonfix :: Name -> Bool -- |
--   qualify A.B x == A.B.x
--   
qualify :: QName -> Name -> QName -- |
--   unqualify A.B.x == x
--   
-- -- The range is preserved. unqualify :: QName -> Name -- |
--   qnameParts A.B.x = [A, B, x]
--   
qnameParts :: QName -> [Name] -- | Turns a qualified name into a TopLevelModuleName. The qualified -- name is assumed to represent a top-level module name. toTopLevelModuleName :: QName -> TopLevelModuleName -- | Turns a top-level module name into a file name with the given suffix. moduleNameToFileName :: TopLevelModuleName -> String -> FilePath -- | Finds the current project's "root" directory, given a project file and -- the corresponding top-level module name. -- -- Example: If the module "A.B.C" is located in the file -- "fooABC.agda", then the root is "foo". -- -- Precondition: The module name must be well-formed. projectRoot :: AbsolutePath -> TopLevelModuleName -> AbsolutePath -- |
--   noName_ = noName noRange
--   
noName_ :: Name -- |
--   noName r = Name r [Hole]
--   
noName :: Range -> Name -- | Check whether a name is the empty name "_". class IsNoName a isNoName :: IsNoName a => a -> Bool instance GHC.Generics.Constructor Agda.Syntax.Concrete.Name.C1_1NamePart instance GHC.Generics.Constructor Agda.Syntax.Concrete.Name.C1_0NamePart instance GHC.Generics.Datatype Agda.Syntax.Concrete.Name.D1NamePart instance GHC.Classes.Ord Agda.Syntax.Concrete.Name.TopLevelModuleName instance GHC.Classes.Eq Agda.Syntax.Concrete.Name.TopLevelModuleName instance GHC.Show.Show Agda.Syntax.Concrete.Name.TopLevelModuleName instance GHC.Classes.Ord Agda.Syntax.Concrete.Name.QName instance GHC.Classes.Eq Agda.Syntax.Concrete.Name.QName instance GHC.Generics.Generic Agda.Syntax.Concrete.Name.NamePart instance Control.DeepSeq.NFData Agda.Syntax.Concrete.Name.Name instance Agda.Syntax.Common.Underscore Agda.Syntax.Concrete.Name.Name instance GHC.Classes.Eq Agda.Syntax.Concrete.Name.Name instance GHC.Classes.Ord Agda.Syntax.Concrete.Name.Name instance GHC.Classes.Eq Agda.Syntax.Concrete.Name.NamePart instance GHC.Classes.Ord Agda.Syntax.Concrete.Name.NamePart instance Agda.Syntax.Common.Underscore Agda.Syntax.Concrete.Name.QName instance Agda.Syntax.Concrete.Name.IsNoName GHC.Base.String instance Agda.Syntax.Concrete.Name.IsNoName Data.ByteString.Internal.ByteString instance Agda.Syntax.Concrete.Name.IsNoName Agda.Syntax.Concrete.Name.Name instance Agda.Syntax.Concrete.Name.IsNoName Agda.Syntax.Concrete.Name.QName instance GHC.Show.Show Agda.Syntax.Concrete.Name.Name instance GHC.Show.Show Agda.Syntax.Concrete.Name.NamePart instance GHC.Show.Show Agda.Syntax.Concrete.Name.QName instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.Name.Name instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.Name.NamePart instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.Name.QName instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.Name.TopLevelModuleName instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Syntax.Concrete.Name.TopLevelModuleName instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Syntax.Concrete.Name.TopLevelModuleName instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Syntax.Concrete.Name.Name instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Syntax.Concrete.Name.NamePart instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Syntax.Concrete.Name.Name instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.Name.Name instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.Name.QName instance Agda.Syntax.Position.SetRange Agda.Syntax.Concrete.Name.Name instance Agda.Syntax.Position.SetRange Agda.Syntax.Concrete.Name.QName instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.Name.QName instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.Name.Name -- | Abstract names carry unique identifiers and stuff. module Agda.Syntax.Abstract.Name -- | A name is a unique identifier and a suggestion for a concrete name. -- The concrete name contains the source location (if any) of the name. -- The source location of the binding site is also recorded. data Name Name :: NameId -> Name -> Range -> Fixity' -> Name [nameId] :: Name -> NameId [nameConcrete] :: Name -> Name [nameBindingSite] :: Name -> Range [nameFixity] :: Name -> Fixity' -- | Qualified names are non-empty lists of names. Equality on qualified -- names are just equality on the last name, i.e. the module part is just -- for show. -- -- The SetRange instance for qualified names sets all individual -- ranges (including those of the module prefix) to the given one. data QName QName :: ModuleName -> Name -> QName [qnameModule] :: QName -> ModuleName [qnameName] :: QName -> Name -- | Something preceeded by a qualified name. data QNamed a QNamed :: QName -> a -> QNamed a [qname] :: QNamed a -> QName [qnamed] :: QNamed a -> a -- | A module name is just a qualified name. -- -- The SetRange instance for module names sets all individual -- ranges to the given one. newtype ModuleName MName :: [Name] -> ModuleName [mnameToList] :: ModuleName -> [Name] -- | Ambiguous qualified names. Used for overloaded constructors. -- -- Invariant: All the names in the list must have the same concrete, -- unqualified name. (This implies that they all have the same -- Range). newtype AmbiguousQName AmbQ :: [QName] -> AmbiguousQName [unAmbQ] :: AmbiguousQName -> [QName] -- | A module is anonymous if the qualification path ends in an underscore. isAnonymousModuleName :: ModuleName -> Bool -- | Sets the ranges of the individual names in the module name to match -- those of the corresponding concrete names. If the concrete names are -- fewer than the number of module name name parts, then the initial name -- parts get the range noRange. -- -- C.D.E `withRangesOf` [A, B] returns C.D.E but with -- ranges set as follows: -- -- -- -- Precondition: The number of module name name parts has to be at least -- as large as the length of the list. withRangesOf :: ModuleName -> [Name] -> ModuleName -- | Like withRangesOf, but uses the name parts (qualifier + name) -- of the qualified name as the list of concrete names. withRangesOfQ :: ModuleName -> QName -> ModuleName mnameFromList :: [Name] -> ModuleName noModuleName :: ModuleName commonParentModule :: ModuleName -> ModuleName -> ModuleName -- | Make a Name from some kind of string. class MkName a where mkName_ = mkName noRange -- | The Range sets the definition site of the name, not the -- use site. mkName :: MkName a => Range -> NameId -> a -> Name mkName_ :: MkName a => NameId -> a -> Name qnameToList :: QName -> [Name] qnameFromList :: [Name] -> QName qnameToMName :: QName -> ModuleName mnameToQName :: ModuleName -> QName showQNameId :: QName -> String -- | Turn a qualified name into a concrete name. This should only be used -- as a fallback when looking up the right concrete name in the scope -- fails. qnameToConcrete :: QName -> QName mnameToConcrete :: ModuleName -> QName -- | Computes the TopLevelModuleName corresponding to the given -- module name, which is assumed to represent a top-level module name. -- -- Precondition: The module name must be well-formed. toTopLevelModuleName :: ModuleName -> TopLevelModuleName qualifyM :: ModuleName -> ModuleName -> ModuleName qualifyQ :: ModuleName -> QName -> QName qualify :: ModuleName -> Name -> QName -- | Convert a Name to a QName (add no module name). qualify_ :: Name -> QName -- | Is the name an operator? isOperator :: QName -> Bool isSubModuleOf :: ModuleName -> ModuleName -> Bool isInModule :: QName -> ModuleName -> Bool -- | Get the next version of the concrete name. For instance, nextName -- "x" = "x₁". The name must not be a NoName. nextName :: Name -> Name -- | An abstract name is empty if its concrete name is empty. -- | Only use this show function in debugging! To convert an -- abstract Name into a string use prettyShow. -- | Only use this show function in debugging! To convert an -- abstract ModuleName into a string use prettyShow. -- | Only use this show function in debugging! To convert an -- abstract QName into a string use prettyShow. -- | The range of an AmbiguousQName is the range of any of its -- disambiguations (they are the same concrete name). -- | The generated names all have the same Fixity': -- noFixity'. -- | Check whether a name is the empty name "_". class IsNoName a isNoName :: IsNoName a => a -> Bool instance GHC.Classes.Eq Agda.Syntax.Abstract.Name.AmbiguousQName instance Data.Traversable.Traversable Agda.Syntax.Abstract.Name.QNamed instance Data.Foldable.Foldable Agda.Syntax.Abstract.Name.QNamed instance GHC.Base.Functor Agda.Syntax.Abstract.Name.QNamed instance GHC.Classes.Ord Agda.Syntax.Abstract.Name.ModuleName instance GHC.Classes.Eq Agda.Syntax.Abstract.Name.ModuleName instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Abstract.Name.QNamed a) instance GHC.Show.Show Agda.Syntax.Abstract.Name.AmbiguousQName instance Agda.Syntax.Abstract.Name.MkName GHC.Base.String instance GHC.Classes.Eq Agda.Syntax.Abstract.Name.Name instance GHC.Classes.Ord Agda.Syntax.Abstract.Name.Name instance Data.Hashable.Class.Hashable Agda.Syntax.Abstract.Name.Name instance GHC.Classes.Eq Agda.Syntax.Abstract.Name.QName instance GHC.Classes.Ord Agda.Syntax.Abstract.Name.QName instance Data.Hashable.Class.Hashable Agda.Syntax.Abstract.Name.QName instance Agda.Syntax.Concrete.Name.IsNoName Agda.Syntax.Abstract.Name.Name instance GHC.Show.Show Agda.Syntax.Abstract.Name.Name instance GHC.Show.Show Agda.Syntax.Abstract.Name.ModuleName instance GHC.Show.Show Agda.Syntax.Abstract.Name.QName instance Agda.Utils.Pretty.Pretty Agda.Syntax.Abstract.Name.Name instance Agda.Utils.Pretty.Pretty Agda.Syntax.Abstract.Name.ModuleName instance Agda.Utils.Pretty.Pretty Agda.Syntax.Abstract.Name.QName instance Agda.Utils.Pretty.Pretty Agda.Syntax.Abstract.Name.AmbiguousQName instance Agda.Utils.Pretty.Pretty a => Agda.Utils.Pretty.Pretty (Agda.Syntax.Abstract.Name.QNamed a) instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.Name.Name instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.Name.ModuleName instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.Name.QName instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.Name.AmbiguousQName instance Agda.Syntax.Position.SetRange Agda.Syntax.Abstract.Name.Name instance Agda.Syntax.Position.SetRange Agda.Syntax.Abstract.Name.QName instance Agda.Syntax.Position.SetRange Agda.Syntax.Abstract.Name.ModuleName instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.Name.Name instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.Name.ModuleName instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.Name.QName instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.Name.AmbiguousQName instance Agda.Utils.Size.Sized Agda.Syntax.Abstract.Name.QName instance Agda.Utils.Size.Sized Agda.Syntax.Abstract.Name.ModuleName instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Syntax.Abstract.Name.Name instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Syntax.Abstract.Name.Name instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Syntax.Abstract.Name.QName instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Syntax.Abstract.Name.QName module Agda.Syntax.Literal data Literal LitInt :: Range -> Integer -> Literal LitFloat :: Range -> Double -> Literal LitString :: Range -> String -> Literal LitChar :: Range -> Char -> Literal LitQName :: Range -> QName -> Literal showString' :: String -> ShowS showChar' :: Char -> ShowS instance GHC.Show.Show Agda.Syntax.Literal.Literal instance Agda.Utils.Pretty.Pretty Agda.Syntax.Literal.Literal instance GHC.Classes.Eq Agda.Syntax.Literal.Literal instance GHC.Classes.Ord Agda.Syntax.Literal.Literal instance Agda.Syntax.Position.HasRange Agda.Syntax.Literal.Literal instance Agda.Syntax.Position.SetRange Agda.Syntax.Literal.Literal instance Agda.Syntax.Position.KillRange Agda.Syntax.Literal.Literal -- | Split tree for transforming pattern clauses into case trees. -- -- The coverage checker generates a split tree from the clauses. The -- clause compiler uses it to transform clauses to case trees. -- -- The initial problem is a set of clauses. The root node designates on -- which argument to split and has subtrees for all the constructors. -- Splitting continues until there is only a single clause left at each -- leaf of the split tree. module Agda.TypeChecking.Coverage.SplitTree type SplitTree = SplitTree' QName type SplitTrees = SplitTrees' QName -- | Abstract case tree shape. data SplitTree' a -- | No more splits coming. We are at a single, all-variable clause. SplittingDone :: Int -> SplitTree' a -- | The number of variables bound in the clause [splitBindings] :: SplitTree' a -> Int -- | A split is necessary. SplitAt :: Int -> SplitTrees' a -> SplitTree' a -- | Arg. no to split at. [splitArg] :: SplitTree' a -> Int -- | Sub split trees. [splitTrees] :: SplitTree' a -> SplitTrees' a -- | Split tree branching. A finite map from constructor names to -- splittrees A list representation seems appropriate, since we are -- expecting not so many constructors per data type, and there is no need -- for random access. type SplitTrees' a = [(a, SplitTree' a)] data SplitTreeLabel a SplitTreeLabel :: Maybe a -> Maybe Int -> Maybe Int -> SplitTreeLabel a -- | Nothing for root of split tree [lblConstructorName] :: SplitTreeLabel a -> Maybe a [lblSplitArg] :: SplitTreeLabel a -> Maybe Int [lblBindings] :: SplitTreeLabel a -> Maybe Int -- | Convert a split tree into a Tree (for printing). toTree :: SplitTree' a -> Tree (SplitTreeLabel a) toTrees :: SplitTrees' a -> Forest (SplitTreeLabel a) newtype CName CName :: String -> CName testSplitTreePrinting :: IO () instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.TypeChecking.Coverage.SplitTree.SplitTree' a) instance GHC.Show.Show a => GHC.Show.Show (Agda.TypeChecking.Coverage.SplitTree.SplitTreeLabel a) instance GHC.Show.Show a => GHC.Show.Show (Agda.TypeChecking.Coverage.SplitTree.SplitTree' a) instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Agda.TypeChecking.Coverage.SplitTree.SplitTree' a) instance GHC.Show.Show Agda.TypeChecking.Coverage.SplitTree.CName instance Test.QuickCheck.Arbitrary.Arbitrary Agda.TypeChecking.Coverage.SplitTree.CName -- | Ranges. module Agda.Interaction.Highlighting.Range -- | Character ranges. The first character in the file has position 1. Note -- that the to position is considered to be outside of the range. -- -- Invariant: from <= to. data Range Range :: Int -> Range [from, to] :: Range -> Int -- | The Range invariant. rangeInvariant :: Range -> Bool -- | Zero or more consecutive and separated ranges. newtype Ranges Ranges :: [Range] -> Ranges -- | The Ranges invariant. rangesInvariant :: Ranges -> Bool -- | True iff the ranges overlap. -- -- The ranges are assumed to be well-formed. overlapping :: Range -> Range -> Bool -- | True iff the range is empty. empty :: Range -> Bool -- | Converts a range to a list of positions. rangeToPositions :: Range -> [Int] -- | Converts several ranges to a list of positions. rangesToPositions :: Ranges -> [Int] -- | Converts a Range to a Ranges. rToR :: Range -> Ranges -- | minus xs ys computes the difference between xs and -- ys: the result contains those positions which are present in -- xs but not in ys. -- -- Linear in the lengths of the input ranges. minus :: Ranges -> Ranges -> Ranges -- | All the properties. tests :: IO Bool instance GHC.Show.Show Agda.Interaction.Highlighting.Range.Ranges instance GHC.Classes.Eq Agda.Interaction.Highlighting.Range.Ranges instance GHC.Show.Show Agda.Interaction.Highlighting.Range.Range instance GHC.Classes.Ord Agda.Interaction.Highlighting.Range.Range instance GHC.Classes.Eq Agda.Interaction.Highlighting.Range.Range instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Interaction.Highlighting.Range.Range instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Interaction.Highlighting.Range.Range instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Interaction.Highlighting.Range.Ranges module Agda.Syntax.Parser.Tokens data Token TokKeyword :: Keyword -> Interval -> Token TokId :: (Interval, String) -> Token TokQId :: [(Interval, String)] -> Token TokLiteral :: Literal -> Token TokSymbol :: Symbol -> Interval -> Token TokString :: (Interval, String) -> Token TokSetN :: (Interval, Integer) -> Token TokTeX :: (Interval, String) -> Token TokComment :: (Interval, String) -> Token TokDummy :: Token TokEOF :: Token data Keyword KwLet :: Keyword KwIn :: Keyword KwWhere :: Keyword KwData :: Keyword KwCoData :: Keyword KwPostulate :: Keyword KwMutual :: Keyword KwAbstract :: Keyword KwPrivate :: Keyword KwInstance :: Keyword KwOpen :: Keyword KwImport :: Keyword KwModule :: Keyword KwPrimitive :: Keyword KwInfix :: Keyword KwInfixL :: Keyword KwInfixR :: Keyword KwWith :: Keyword KwRewrite :: Keyword KwSet :: Keyword KwProp :: Keyword KwForall :: Keyword KwRecord :: Keyword KwConstructor :: Keyword KwField :: Keyword KwInductive :: Keyword KwCoInductive :: Keyword KwHiding :: Keyword KwUsing :: Keyword KwRenaming :: Keyword KwTo :: Keyword KwPublic :: Keyword KwOPTIONS :: Keyword KwBUILTIN :: Keyword KwLINE :: Keyword KwCOMPILED_DATA :: Keyword KwCOMPILED_TYPE :: Keyword KwCOMPILED :: Keyword KwCOMPILED_EXPORT :: Keyword KwCOMPILED_EPIC :: Keyword KwCOMPILED_JS :: Keyword KwIMPORT :: Keyword KwIMPOSSIBLE :: Keyword KwETA :: Keyword KwSTATIC :: Keyword KwNO_TERMINATION_CHECK :: Keyword KwTERMINATING :: Keyword KwNON_TERMINATING :: Keyword KwMEASURE :: Keyword KwREWRITE :: Keyword KwQuoteGoal :: Keyword KwQuoteContext :: Keyword KwQuote :: Keyword KwQuoteTerm :: Keyword KwUnquote :: Keyword KwUnquoteDecl :: Keyword KwSyntax :: Keyword KwPatternSyn :: Keyword KwTactic :: Keyword layoutKeywords :: [Keyword] data Symbol SymDot :: Symbol SymSemi :: Symbol SymVirtualSemi :: Symbol SymBar :: Symbol SymColon :: Symbol SymArrow :: Symbol SymEqual :: Symbol SymLambda :: Symbol SymUnderscore :: Symbol SymQuestionMark :: Symbol SymAs :: Symbol SymOpenParen :: Symbol SymCloseParen :: Symbol SymDoubleOpenBrace :: Symbol SymDoubleCloseBrace :: Symbol SymOpenBrace :: Symbol SymCloseBrace :: Symbol SymOpenVirtualBrace :: Symbol SymCloseVirtualBrace :: Symbol SymOpenPragma :: Symbol SymClosePragma :: Symbol SymEllipsis :: Symbol SymDotDot :: Symbol -- | A misplaced end-comment "-}". SymEndComment :: Symbol instance GHC.Show.Show Agda.Syntax.Parser.Tokens.Token instance GHC.Classes.Eq Agda.Syntax.Parser.Tokens.Token instance GHC.Show.Show Agda.Syntax.Parser.Tokens.Symbol instance GHC.Classes.Eq Agda.Syntax.Parser.Tokens.Symbol instance GHC.Show.Show Agda.Syntax.Parser.Tokens.Keyword instance GHC.Classes.Eq Agda.Syntax.Parser.Tokens.Keyword instance Agda.Syntax.Position.HasRange Agda.Syntax.Parser.Tokens.Token -- | As a concrete name, a notation is a non-empty list of alternating -- IdParts and holes. In contrast to concrete names, holes can be -- binders. -- -- Example: syntax fmap (λ x → e) xs = for x ∈ xs return e -- -- The declared notation for fmap is for_∈_return_ -- where the first hole is a binder. module Agda.Syntax.Notation -- | Data type constructed in the Happy parser; converted to GenPart -- before it leaves the Happy code. data HoleName -- | x -> y; 1st argument is the bound name (unused for now). LambdaHole :: RawName -> RawName -> HoleName [_bindHoleName] :: HoleName -> RawName [holeName] :: HoleName -> RawName -- | Simple named hole with hiding. ExprHole :: RawName -> HoleName [holeName] :: HoleName -> RawName -- | Is the hole a binder? isLambdaHole :: HoleName -> Bool -- | Notation as provided by the syntax declaration. type Notation = [GenPart] -- | Part of a Notation data GenPart -- | Argument is the position of the hole (with binding) where the binding -- should occur. BindHole :: Int -> GenPart -- | Argument is where the expression should go. NormalHole :: (NamedArg () Int) -> GenPart IdPart :: RawName -> GenPart -- | Get a flat list of identifier parts of a notation. stringParts :: Notation -> [RawName] -- | Target argument position of a part (Nothing if it is not a hole). holeTarget :: GenPart -> Maybe Int -- | Is the part a hole? isAHole :: GenPart -> Bool -- | Is the part a binder? isBindingHole :: GenPart -> Bool -- | Classification of notations. data NotationKind -- | Ex: _bla_blub_. InfixNotation :: NotationKind -- | Ex: _bla_blub. PrefixNotation :: NotationKind -- | Ex: bla_blub_. PostfixNotation :: NotationKind -- | Ex: bla_blub. NonfixNotation :: NotationKind NoNotation :: NotationKind -- | Classify a notation by presence of leading and/or trailing hole. notationKind :: Notation -> NotationKind -- | From notation with names to notation with indices. -- -- Example: ids = ["for", "x", "∈", "xs", "return", "e"] holes = [ -- LambdaHole "x" "e", ExprHole "xs" ] creates the notation [ -- IdPart "for" , BindHole 0 , IdPart "∈" , NormalHole 1 , IdPart -- "return" , NormalHole 0 ] mkNotation :: [NamedArg c HoleName] -> [RawName] -> Either String Notation -- | No notation by default. defaultNotation :: Notation -- | No notation by default. noNotation :: Notation instance GHC.Show.Show Agda.Syntax.Notation.NotationKind instance GHC.Classes.Eq Agda.Syntax.Notation.NotationKind instance GHC.Classes.Ord Agda.Syntax.Notation.GenPart instance GHC.Classes.Eq Agda.Syntax.Notation.GenPart instance GHC.Show.Show Agda.Syntax.Notation.GenPart instance Agda.Syntax.Position.KillRange Agda.Syntax.Notation.GenPart -- | Definitions for fixity, precedence levels, and declared syntax. module Agda.Syntax.Fixity -- | The notation is handled as the fixity in the renamer. Hence, they are -- grouped together in this type. data Fixity' Fixity' :: Fixity -> Notation -> Fixity' [theFixity] :: Fixity' -> Fixity [theNotation] :: Fixity' -> Notation -- | Decorating something with Fixity'. data ThingWithFixity x ThingWithFixity :: x -> Fixity' -> ThingWithFixity x -- | All the notation information related to a name. data NewNotation NewNotation :: QName -> Set Name -> Fixity -> Notation -> NewNotation [notaName] :: NewNotation -> QName -- | The names the syntax and/or fixity belong to. -- -- Invariant: The set is non-empty. Every name in the list matches -- notaName. [notaNames] :: NewNotation -> Set Name -- | Associativity and precedence (fixity) of the names. [notaFixity] :: NewNotation -> Fixity -- | Syntax associated with the names. [notation] :: NewNotation -> Notation -- | If an operator has no specific notation, then it is computed from its -- name. namesToNotation :: QName -> Name -> NewNotation -- | Return the IdParts of a notation, the first part qualified, the -- other parts unqualified. This allows for qualified use of operators, -- e.g., M.for x ∈ xs return e, or x ℕ.+ y. notationNames :: NewNotation -> [QName] -- | Create a Notation (without binders) from a concrete -- Name. Does the obvious thing: Holes become -- NormalHoles, Ids become IdParts. If Name -- has no Holes, it returns noNotation. syntaxOf :: Name -> Notation defaultFixity' :: Fixity' noFixity' :: Fixity' -- | Merges all NewNotations that have the same notation. -- -- If all NewNotations with a given notation have the same fixity, -- then this fixity is preserved, and otherwise it is replaced by -- defaultFixity. -- -- Precondition: No Name may occur in more than one list element. -- Every NewNotation must have the same notaName. -- -- Postcondition: No Name occurs in more than one list element. mergeNotations :: [NewNotation] -> [NewNotation] -- | Associativity. data Associativity NonAssoc :: Associativity LeftAssoc :: Associativity RightAssoc :: Associativity -- | Fixity of operators. data Fixity Fixity :: Range -> Integer -> Associativity -> Fixity [fixityRange] :: Fixity -> Range [fixityLevel] :: Fixity -> Integer [fixityAssoc] :: Fixity -> Associativity -- | The default fixity. Currently defined to be NonAssoc -- 20. defaultFixity :: Fixity -- | Hack used for syntax facility. noFixity :: Fixity -- | Precedence is associated with a context. data Precedence TopCtx :: Precedence FunctionSpaceDomainCtx :: Precedence LeftOperandCtx :: Fixity -> Precedence RightOperandCtx :: Fixity -> Precedence FunctionCtx :: Precedence ArgumentCtx :: Precedence InsideOperandCtx :: Precedence WithFunCtx :: Precedence WithArgCtx :: Precedence DotPatternCtx :: Precedence -- | The precedence corresponding to a possibly hidden argument. hiddenArgumentCtx :: Hiding -> Precedence -- | Do we need to bracket an operator application of the given fixity in a -- context with the given precedence. opBrackets :: Fixity -> Precedence -> Bool -- | Does a lambda-like thing (lambda, let or pi) need brackets in the -- given context? A peculiar thing with lambdas is that they don't need -- brackets in certain right operand contexts. However, we insert -- brackets anyway, for the following reasons: -- -- lamBrackets :: Precedence -> Bool -- | Does a function application need brackets? appBrackets :: Precedence -> Bool -- | Does a with application need brackets? withAppBrackets :: Precedence -> Bool -- | Does a function space need brackets? piBrackets :: Precedence -> Bool roundFixBrackets :: Precedence -> Bool instance GHC.Show.Show x => GHC.Show.Show (Agda.Syntax.Fixity.ThingWithFixity x) instance Data.Traversable.Traversable Agda.Syntax.Fixity.ThingWithFixity instance Data.Foldable.Foldable Agda.Syntax.Fixity.ThingWithFixity instance GHC.Base.Functor Agda.Syntax.Fixity.ThingWithFixity instance GHC.Show.Show Agda.Syntax.Fixity.NewNotation instance GHC.Show.Show Agda.Syntax.Fixity.Precedence instance GHC.Show.Show Agda.Syntax.Fixity.Fixity instance GHC.Classes.Eq Agda.Syntax.Fixity.Fixity' instance GHC.Show.Show Agda.Syntax.Fixity.Fixity' instance GHC.Show.Show Agda.Syntax.Fixity.Associativity instance GHC.Classes.Ord Agda.Syntax.Fixity.Associativity instance GHC.Classes.Eq Agda.Syntax.Fixity.Associativity instance GHC.Classes.Eq Agda.Syntax.Fixity.Fixity instance GHC.Classes.Ord Agda.Syntax.Fixity.Fixity instance Agda.Syntax.Position.HasRange Agda.Syntax.Fixity.Fixity instance Agda.Syntax.Position.KillRange Agda.Syntax.Fixity.Fixity instance Agda.Syntax.Position.KillRange Agda.Syntax.Fixity.Fixity' instance Agda.Syntax.Position.KillRange x => Agda.Syntax.Position.KillRange (Agda.Syntax.Fixity.ThingWithFixity x) -- | The concrete syntax is a raw representation of the program text -- without any desugaring at all. This is what the parser produces. The -- idea is that if we figure out how to keep the concrete syntax around, -- it can be printed exactly as the user wrote it. module Agda.Syntax.Concrete -- | Concrete expressions. Should represent exactly what the user wrote. data Expr -- | ex: x Ident :: QName -> Expr -- | ex: 1 or "foo" Lit :: Literal -> Expr -- | ex: ? or {! ... !} QuestionMark :: !Range -> (Maybe Nat) -> Expr -- | ex: _ or _A_5 Underscore :: !Range -> (Maybe String) -> Expr -- | before parsing operators RawApp :: !Range -> [Expr] -> Expr -- | ex: e e, e {e}, or e {x = e} App :: !Range -> Expr -> (NamedArg Expr) -> Expr -- | ex: e + e The QName is possibly ambiguous, but it must -- correspond to one of the names in the set. OpApp :: !Range -> QName -> (Set Name) -> [NamedArg (OpApp Expr)] -> Expr -- | ex: e | e1 | .. | en WithApp :: !Range -> Expr -> [Expr] -> Expr -- | ex: {e} or {x=e} HiddenArg :: !Range -> (Named_ Expr) -> Expr -- | ex: {{e}} or {{x=e}} InstanceArg :: !Range -> (Named_ Expr) -> Expr -- | ex: \x {y} -> e or \(x:A){y:B} -> e Lam :: !Range -> [LamBinding] -> Expr -> Expr -- | ex: \ () AbsurdLam :: !Range -> Hiding -> Expr -- | ex: \ { p11 .. p1a -> e1 ; .. ; pn1 .. pnz -> en } ExtendedLam :: !Range -> [(LHS, RHS, WhereClause)] -> Expr -- | ex: e -> e or .e -> e (NYI: {e} -> -- e) Fun :: !Range -> Expr -> Expr -> Expr -- | ex: (xs:e) -> e or {xs:e} -> e Pi :: Telescope -> Expr -> Expr -- | ex: Set Set :: !Range -> Expr -- | ex: Prop Prop :: !Range -> Expr -- | ex: Set0, Set1, .. SetN :: !Range -> Integer -> Expr -- | ex: record {x = a; y = b} Rec :: !Range -> [(Name, Expr)] -> Expr -- | ex: record e {x = a; y = b} RecUpdate :: !Range -> Expr -> [(Name, Expr)] -> Expr -- | ex: let Ds in e Let :: !Range -> [Declaration] -> Expr -> Expr -- | ex: (e) Paren :: !Range -> Expr -> Expr -- | ex: () or {}, only in patterns Absurd :: !Range -> Expr -- | ex: x@p, only in patterns As :: !Range -> Name -> Expr -> Expr -- | ex: .p, only in patterns Dot :: !Range -> Expr -> Expr -- | only used for printing telescopes ETel :: Telescope -> Expr -- | ex: quoteGoal x in e QuoteGoal :: !Range -> Name -> Expr -> Expr -- | ex: quoteContext ctx in e QuoteContext :: !Range -> Name -> Expr -> Expr -- | ex: quote, should be applied to a name Quote :: !Range -> Expr -- | ex: quoteTerm, should be applied to a term QuoteTerm :: !Range -> Expr -- |
--   tactic solve | subgoal1 | .. | subgoalN
--   
Tactic :: !Range -> Expr -> [Expr] -> Expr -- | ex: unquote, should be applied to a term of type -- Term Unquote :: !Range -> Expr -- | to print irrelevant things DontCare :: Expr -> Expr -- | ex: a = b, used internally in the parser Equal :: !Range -> Expr -> Expr -> Expr data OpApp e -- | An abstraction inside a special syntax declaration (see Issue 358 why -- we introduce this). SyntaxBindingLambda :: !Range -> [LamBinding] -> e -> OpApp e Ordinary :: e -> OpApp e fromOrdinary :: e -> OpApp e -> e appView :: Expr -> AppView -- | The Expr is not an application. data AppView AppView :: Expr -> [NamedArg Expr] -> AppView -- | A lambda binding is either domain free or typed. type LamBinding = LamBinding' TypedBindings data LamBinding' a -- | . x or {x} or .x or .{x} or -- {.x} DomainFree :: ArgInfo -> BoundName -> LamBinding' a -- | . (xs : e) or {xs : e} DomainFull :: a -> LamBinding' a -- | A sequence of typed bindings with hiding information. Appears in -- dependent function spaces, typed lambdas, and telescopes. -- -- If the individual binding contains hiding information as well, the -- Hiding in TypedBindings must be the unit -- NotHidden. type TypedBindings = TypedBindings' TypedBinding data TypedBindings' a -- | . (xs : e) or {xs : e} or something like (x {y} -- _ : e). TypedBindings :: !Range -> (Arg a) -> TypedBindings' a -- | A typed binding. type TypedBinding = TypedBinding' Expr data TypedBinding' e -- | Binding (x1 ... xn : A). TBind :: !Range -> [WithHiding BoundName] -> e -> TypedBinding' e -- | Let binding (let Ds) or (open M args). TLet :: !Range -> [Declaration] -> TypedBinding' e -- | Color a TypeBinding. Used by Pretty. data ColoredTypedBinding WithColors :: [Color] -> TypedBinding -> ColoredTypedBinding data BoundName BName :: Name -> Name -> Fixity' -> BoundName [boundName] :: BoundName -> Name -- | for implicit function types the label matters and can't be -- alpha-renamed [boundLabel] :: BoundName -> Name [bnameFixity] :: BoundName -> Fixity' mkBoundName_ :: Name -> BoundName mkBoundName :: Name -> Fixity' -> BoundName -- | A telescope is a sequence of typed bindings. Bound variables are in -- scope in later types. type Telescope = [TypedBindings] countTelVars :: Telescope -> Nat -- | The representation type of a declaration. The comments indicate which -- type in the intended family the constructor targets. data Declaration -- | Axioms and functions can be irrelevant. (Hiding should be NotHidden) TypeSig :: ArgInfo -> Name -> Expr -> Declaration -- | Record field, can be hidden and/or irrelevant. Field :: Name -> (Arg Expr) -> Declaration FunClause :: LHS -> RHS -> WhereClause -> Declaration -- | lone data signature in mutual block DataSig :: !Range -> Induction -> Name -> [LamBinding] -> Expr -> Declaration Data :: !Range -> Induction -> Name -> [LamBinding] -> (Maybe Expr) -> [Constructor] -> Declaration -- | lone record signature in mutual block RecordSig :: !Range -> Name -> [LamBinding] -> Expr -> Declaration -- | The optional name is a name for the record constructor. Record :: !Range -> Name -> (Maybe (Ranged Induction)) -> (Maybe Name) -> [LamBinding] -> (Maybe Expr) -> [Declaration] -> Declaration Infix :: Fixity -> [Name] -> Declaration -- | notation declaration for a name Syntax :: Name -> Notation -> Declaration PatternSyn :: !Range -> Name -> [Arg Name] -> Pattern -> Declaration Mutual :: !Range -> [Declaration] -> Declaration Abstract :: !Range -> [Declaration] -> Declaration Private :: !Range -> [Declaration] -> Declaration InstanceB :: !Range -> [Declaration] -> Declaration Postulate :: !Range -> [TypeSignatureOrInstanceBlock] -> Declaration Primitive :: !Range -> [TypeSignature] -> Declaration Open :: !Range -> QName -> ImportDirective -> Declaration Import :: !Range -> QName -> (Maybe AsName) -> OpenShortHand -> ImportDirective -> Declaration ModuleMacro :: !Range -> Name -> ModuleApplication -> OpenShortHand -> ImportDirective -> Declaration Module :: !Range -> QName -> [TypedBindings] -> [Declaration] -> Declaration UnquoteDecl :: !Range -> Name -> Expr -> Declaration Pragma :: Pragma -> Declaration data ModuleApplication -- |
--   tel. M args
--   
SectionApp :: Range -> [TypedBindings] -> Expr -> ModuleApplication -- |
--   M {{...}}
--   
RecordModuleIFS :: Range -> QName -> ModuleApplication -- | Just type signatures. type TypeSignature = Declaration -- | Just type signatures or instance blocks. type TypeSignatureOrInstanceBlock = Declaration -- | A data constructor declaration is just a type signature. type Constructor = TypeSignature -- | The things you are allowed to say when you shuffle names between name -- spaces (i.e. in import, namespace, or open -- declarations). data ImportDirective ImportDirective :: !Range -> UsingOrHiding -> [Renaming] -> Bool -> ImportDirective [importDirRange] :: ImportDirective -> !Range [usingOrHiding] :: ImportDirective -> UsingOrHiding [renaming] :: ImportDirective -> [Renaming] -- | Only for open. Exports the opened names from the current -- module. [publicOpen] :: ImportDirective -> Bool data UsingOrHiding Hiding :: [ImportedName] -> UsingOrHiding Using :: [ImportedName] -> UsingOrHiding -- | An imported name can be a module or a defined name data ImportedName ImportedModule :: Name -> ImportedName [importedName] :: ImportedName -> Name ImportedName :: Name -> ImportedName [importedName] :: ImportedName -> Name data Renaming Renaming :: ImportedName -> Name -> Range -> Renaming -- | Rename from this name. [renFrom] :: Renaming -> ImportedName -- | To this one. [renTo] :: Renaming -> Name -- | The range of the "to" keyword. Retained for highlighting purposes. [renToRange] :: Renaming -> Range data AsName AsName :: Name -> Range -> AsName -- | The "as" name. [asName] :: AsName -> Name -- | The range of the "as" keyword. Retained for highlighting purposes. [asRange] :: AsName -> Range -- | Default is directive is private (use everything, but do not -- export). defaultImportDir :: ImportDirective data OpenShortHand DoOpen :: OpenShortHand DontOpen :: OpenShortHand type RewriteEqn = Expr type WithExpr = Expr -- | Left hand sides can be written in infix style. For example: -- --
--   n + suc m = suc (n + m)
--   (f ∘ g) x = f (g x)
--   
-- -- We use fixity information to see which name is actually defined. data LHS -- | original pattern, with-patterns, rewrite equations and -- with-expressions LHS :: Pattern -> [Pattern] -> [RewriteEqn] -> [WithExpr] -> LHS -- |
--   f ps
--   
[lhsOriginalPattern] :: LHS -> Pattern -- | | p (many) [lhsWithPattern] :: LHS -> [Pattern] -- | rewrite e (many) [lhsRewriteEqn] :: LHS -> [RewriteEqn] -- | with e (many) [lhsWithExpr] :: LHS -> [WithExpr] -- | new with-patterns, rewrite equations and with-expressions Ellipsis :: Range -> [Pattern] -> [RewriteEqn] -> [WithExpr] -> LHS -- | Concrete patterns. No literals in patterns at the moment. data Pattern -- | c or x IdentP :: QName -> Pattern -- |
--   quote
--   
QuoteP :: !Range -> Pattern -- | p p' or p {x = p'} AppP :: Pattern -> (NamedArg Pattern) -> Pattern -- | p1..pn before parsing operators RawAppP :: !Range -> [Pattern] -> Pattern -- | eg: p => p' for operator _=>_ The QName -- is possibly ambiguous, but it must correspond to one of the names in -- the set. OpAppP :: !Range -> QName -> (Set Name) -> [NamedArg Pattern] -> Pattern -- | {p} or {x = p} HiddenP :: !Range -> (Named_ Pattern) -> Pattern -- | {{p}} or {{x = p}} InstanceP :: !Range -> (Named_ Pattern) -> Pattern -- |
--   (p)
--   
ParenP :: !Range -> Pattern -> Pattern -- |
--   _
--   
WildP :: !Range -> Pattern -- |
--   ()
--   
AbsurdP :: !Range -> Pattern -- | x@p unused AsP :: !Range -> Name -> Pattern -> Pattern -- |
--   .e
--   
DotP :: !Range -> Expr -> Pattern -- | 0, 1, etc. LitP :: Literal -> Pattern -- | Processed (scope-checked) intermediate form of the core f ps -- of LHS. Corresponds to lhsOriginalPattern. data LHSCore LHSHead :: Name -> [NamedArg Pattern] -> LHSCore -- |
--   f
--   
[lhsDefName] :: LHSCore -> Name -- |
--   ps
--   
[lhsPats] :: LHSCore -> [NamedArg Pattern] LHSProj :: QName -> [NamedArg Pattern] -> NamedArg LHSCore -> [NamedArg Pattern] -> LHSCore -- | record projection identifier [lhsDestructor] :: LHSCore -> QName -- | side patterns [lhsPatsLeft] :: LHSCore -> [NamedArg Pattern] -- | main branch [lhsFocus] :: LHSCore -> NamedArg LHSCore -- | side patterns [lhsPatsRight] :: LHSCore -> [NamedArg Pattern] type RHS = RHS' Expr data RHS' e -- | No right hand side because of absurd match. AbsurdRHS :: RHS' e RHS :: e -> RHS' e type WhereClause = WhereClause' [Declaration] data WhereClause' decls -- | No where clauses. NoWhere :: WhereClause' decls -- | Ordinary where. AnyWhere :: decls -> WhereClause' decls -- | Named where: module M where. SomeWhere :: Name -> decls -> WhereClause' decls data Pragma OptionsPragma :: !Range -> [String] -> Pragma BuiltinPragma :: !Range -> String -> Expr -> Pragma RewritePragma :: !Range -> QName -> Pragma CompiledDataPragma :: !Range -> QName -> String -> [String] -> Pragma CompiledTypePragma :: !Range -> QName -> String -> Pragma CompiledPragma :: !Range -> QName -> String -> Pragma CompiledExportPragma :: !Range -> QName -> String -> Pragma CompiledEpicPragma :: !Range -> QName -> String -> Pragma CompiledJSPragma :: !Range -> QName -> String -> Pragma StaticPragma :: !Range -> QName -> Pragma -- | Invariant: The string must be a valid Haskell module name. ImportPragma :: !Range -> String -> Pragma ImpossiblePragma :: !Range -> Pragma EtaPragma :: !Range -> QName -> Pragma TerminationCheckPragma :: !Range -> (TerminationCheck Name) -> Pragma -- | Modules: Top-level pragmas plus other top-level declarations. type Module = ([Pragma], [Declaration]) -- | Decorating something with Fixity'. data ThingWithFixity x ThingWithFixity :: x -> Fixity' -> ThingWithFixity x -- | Computes the top-level module name. -- -- Precondition: The Module has to be well-formed. topLevelModuleName :: Module -> TopLevelModuleName -- | Get all the identifiers in a pattern in left-to-right order. patternNames :: Pattern -> [Name] -- | Get all the identifiers in a pattern in left-to-right order. patternQNames :: Pattern -> [QName] mapLhsOriginalPattern :: (Pattern -> Pattern) -> LHS -> LHS type Color = Expr type Arg a = Arg Color a type NamedArg a = NamedArg Color a type ArgInfo = ArgInfo Color instance Data.Traversable.Traversable Agda.Syntax.Concrete.OpApp instance Data.Foldable.Foldable Agda.Syntax.Concrete.OpApp instance GHC.Base.Functor Agda.Syntax.Concrete.OpApp instance Data.Traversable.Traversable Agda.Syntax.Concrete.LamBinding' instance Data.Foldable.Foldable Agda.Syntax.Concrete.LamBinding' instance GHC.Base.Functor Agda.Syntax.Concrete.LamBinding' instance Data.Traversable.Traversable Agda.Syntax.Concrete.TypedBindings' instance Data.Foldable.Foldable Agda.Syntax.Concrete.TypedBindings' instance GHC.Base.Functor Agda.Syntax.Concrete.TypedBindings' instance Data.Traversable.Traversable Agda.Syntax.Concrete.TypedBinding' instance Data.Foldable.Foldable Agda.Syntax.Concrete.TypedBinding' instance GHC.Base.Functor Agda.Syntax.Concrete.TypedBinding' instance GHC.Show.Show Agda.Syntax.Concrete.OpenShortHand instance GHC.Classes.Eq Agda.Syntax.Concrete.OpenShortHand instance GHC.Show.Show Agda.Syntax.Concrete.AsName instance GHC.Classes.Ord Agda.Syntax.Concrete.ImportedName instance GHC.Classes.Eq Agda.Syntax.Concrete.ImportedName instance Data.Traversable.Traversable Agda.Syntax.Concrete.WhereClause' instance Data.Foldable.Foldable Agda.Syntax.Concrete.WhereClause' instance GHC.Base.Functor Agda.Syntax.Concrete.WhereClause' instance Data.Traversable.Traversable Agda.Syntax.Concrete.RHS' instance Data.Foldable.Foldable Agda.Syntax.Concrete.RHS' instance GHC.Base.Functor Agda.Syntax.Concrete.RHS' instance Control.DeepSeq.NFData Agda.Syntax.Concrete.Expr instance Control.DeepSeq.NFData Agda.Syntax.Concrete.Pattern instance Control.DeepSeq.NFData Agda.Syntax.Concrete.LHSCore instance GHC.Show.Show Agda.Syntax.Concrete.ImportedName instance Agda.Syntax.Common.LensRelevance Agda.Syntax.Concrete.TypedBindings instance Agda.Syntax.Common.LensHiding Agda.Syntax.Concrete.TypedBindings instance Agda.Syntax.Common.LensHiding Agda.Syntax.Concrete.LamBinding instance Agda.Syntax.Position.HasRange e => Agda.Syntax.Position.HasRange (Agda.Syntax.Concrete.OpApp e) instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.Expr instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.TypedBindings instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.TypedBinding instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.LamBinding instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.BoundName instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.WhereClause instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.ModuleApplication instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.Declaration instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.LHS instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.LHSCore instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.RHS instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.Pragma instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.UsingOrHiding instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.ImportDirective instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.ImportedName instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.Renaming instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.AsName instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.Pattern instance Agda.Syntax.Position.SetRange Agda.Syntax.Concrete.TypedBindings instance Agda.Syntax.Position.SetRange Agda.Syntax.Concrete.Pattern instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.AsName instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.BoundName instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.Declaration instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.Expr instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.ImportDirective instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.ImportedName instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.LamBinding instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.LHS instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.ModuleApplication instance Agda.Syntax.Position.KillRange e => Agda.Syntax.Position.KillRange (Agda.Syntax.Concrete.OpApp e) instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.Pattern instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.Pragma instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.Renaming instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.RHS instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.TypedBinding instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.TypedBindings instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.UsingOrHiding instance Agda.Syntax.Position.KillRange Agda.Syntax.Concrete.WhereClause -- | This module defines the notion of a scope and operations on scopes. module Agda.Syntax.Scope.Base -- | A scope is a named collection of names partitioned into public and -- private names. data Scope Scope :: ModuleName -> [ModuleName] -> ScopeNameSpaces -> Map QName ModuleName -> Bool -> Scope [scopeName] :: Scope -> ModuleName [scopeParents] :: Scope -> [ModuleName] [scopeNameSpaces] :: Scope -> ScopeNameSpaces [scopeImports] :: Scope -> Map QName ModuleName [scopeDatatypeModule] :: Scope -> Bool -- | See Access. data NameSpaceId -- | Things not exported by this module. PrivateNS :: NameSpaceId -- | Things defined and exported by this module. PublicNS :: NameSpaceId -- | Things from open public, exported by this module. ImportedNS :: NameSpaceId -- | Visible (as qualified) from outside, but not exported when opening the -- module. Used for qualified constructors. OnlyQualifiedNS :: NameSpaceId type ScopeNameSpaces = [(NameSpaceId, NameSpace)] localNameSpace :: Access -> NameSpaceId nameSpaceAccess :: NameSpaceId -> Access -- | Get a NameSpace from Scope. scopeNameSpace :: NameSpaceId -> Scope -> NameSpace -- | A lens for scopeNameSpaces updateScopeNameSpaces :: (ScopeNameSpaces -> ScopeNameSpaces) -> Scope -> Scope -- | `Monadic' lens (Functor sufficient). updateScopeNameSpacesM :: (Functor m) => (ScopeNameSpaces -> m ScopeNameSpaces) -> Scope -> m Scope -- | The complete information about the scope at a particular program point -- includes the scope stack, the local variables, and the context -- precedence. data ScopeInfo ScopeInfo :: ModuleName -> Map ModuleName Scope -> LocalVars -> Precedence -> ScopeInfo [scopeCurrent] :: ScopeInfo -> ModuleName [scopeModules] :: ScopeInfo -> Map ModuleName Scope [scopeLocals] :: ScopeInfo -> LocalVars [scopePrecedence] :: ScopeInfo -> Precedence -- | Local variables. type LocalVars = AssocList Name LocalVar -- | A local variable can be shadowed by an import. In case of reference to -- a shadowed variable, we want to report a scope error. data LocalVar -- | Unique ID of local variable. LocalVar :: Name -> LocalVar [localVar] :: LocalVar -> Name -- | This local variable is shadowed by one or more imports. (List not -- empty). ShadowedVar :: Name -> [AbstractName] -> LocalVar [localVar] :: LocalVar -> Name [localShadowedBy] :: LocalVar -> [AbstractName] -- | We show shadowed variables as prefixed by a ".", as not in scope. -- | Shadow a local name by a non-empty list of imports. shadowLocal :: [AbstractName] -> LocalVar -> LocalVar -- | Project name of unshadowed local variable. notShadowedLocal :: LocalVar -> Maybe Name -- | Get all locals that are not shadowed. notShadowedLocals :: LocalVars -> AssocList Name Name -- | Lens for scopeLocals. updateScopeLocals :: (LocalVars -> LocalVars) -> ScopeInfo -> ScopeInfo setScopeLocals :: LocalVars -> ScopeInfo -> ScopeInfo -- | A NameSpace contains the mappings from concrete names that -- the user can write to the abstract fully qualified names that the type -- checker wants to read. data NameSpace NameSpace :: NamesInScope -> ModulesInScope -> NameSpace -- | Maps concrete names to a list of abstract names. [nsNames] :: NameSpace -> NamesInScope -- | Maps concrete module names to a list of abstract module names. [nsModules] :: NameSpace -> ModulesInScope type ThingsInScope a = Map Name [a] type NamesInScope = ThingsInScope AbstractName type ModulesInScope = ThingsInScope AbstractModule -- | Set of types consisting of exactly AbstractName and -- AbstractModule. -- -- A GADT just for some dependent-types trickery. data InScopeTag a NameTag :: InScopeTag AbstractName ModuleTag :: InScopeTag AbstractModule -- | Type class for some dependent-types trickery. class Eq a => InScope a inScopeTag :: InScope a => InScopeTag a -- | inNameSpace selects either the name map or the module name -- map from a NameSpace. What is selected is determined by result -- type (using the dependent-type trickery). inNameSpace :: InScope a => NameSpace -> ThingsInScope a -- | For the sake of parsing left-hand sides, we distinguish constructor -- and record field names from defined names. data KindOfName -- | Constructor name. ConName :: KindOfName -- | Record field name. FldName :: KindOfName -- | Ordinary defined name. DefName :: KindOfName -- | Name of a pattern synonym. PatternSynName :: KindOfName -- | A name that can only quoted. QuotableName :: KindOfName -- | A list containing all name kinds. allKindsOfNames :: [KindOfName] -- | Where does a name come from? -- -- This information is solely for reporting to the user, see -- whyInScope. data WhyInScope -- | Defined in this module. Defined :: WhyInScope -- | Imported from another module. Opened :: QName -> WhyInScope -> WhyInScope -- | Imported by a module application. Applied :: QName -> WhyInScope -> WhyInScope -- | A decoration of QName. data AbstractName AbsName :: QName -> KindOfName -> WhyInScope -> AbstractName -- | The resolved qualified name. [anameName] :: AbstractName -> QName -- | The kind (definition, constructor, record field etc.). [anameKind] :: AbstractName -> KindOfName -- | Explanation where this name came from. [anameLineage] :: AbstractName -> WhyInScope -- | A decoration of abstract syntax module names. data AbstractModule AbsModule :: ModuleName -> WhyInScope -> AbstractModule -- | The resolved module name. [amodName] :: AbstractModule -> ModuleName -- | Explanation where this name came from. [amodLineage] :: AbstractModule -> WhyInScope -- | Van Laarhoven lens on anameName. lensAnameName :: Functor m => (QName -> m QName) -> AbstractName -> m AbstractName -- | Van Laarhoven lens on amodName. lensAmodName :: Functor m => (ModuleName -> m ModuleName) -> AbstractModule -> m AbstractModule mergeNames :: Eq a => ThingsInScope a -> ThingsInScope a -> ThingsInScope a -- | The empty name space. emptyNameSpace :: NameSpace -- | Map functions over the names and modules in a name space. mapNameSpace :: (NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope) -> NameSpace -> NameSpace -- | Zip together two name spaces. zipNameSpace :: (NamesInScope -> NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope -> ModulesInScope) -> NameSpace -> NameSpace -> NameSpace -- | Map monadic function over a namespace. mapNameSpaceM :: Applicative m => (NamesInScope -> m NamesInScope) -> (ModulesInScope -> m ModulesInScope) -> NameSpace -> m NameSpace -- | The empty scope. emptyScope :: Scope -- | The empty scope info. emptyScopeInfo :: ScopeInfo -- | Map functions over the names and modules in a scope. mapScope :: (NameSpaceId -> NamesInScope -> NamesInScope) -> (NameSpaceId -> ModulesInScope -> ModulesInScope) -> Scope -> Scope -- | Same as mapScope but applies the same function to all name -- spaces. mapScope_ :: (NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope) -> Scope -> Scope -- | Map monadic functions over the names and modules in a scope. mapScopeM :: (Functor m, Applicative m) => (NameSpaceId -> NamesInScope -> m NamesInScope) -> (NameSpaceId -> ModulesInScope -> m ModulesInScope) -> Scope -> m Scope -- | Same as mapScopeM but applies the same function to both the -- public and private name spaces. mapScopeM_ :: (Functor m, Applicative m) => (NamesInScope -> m NamesInScope) -> (ModulesInScope -> m ModulesInScope) -> Scope -> m Scope -- | Zip together two scopes. The resulting scope has the same name as the -- first scope. zipScope :: (NameSpaceId -> NamesInScope -> NamesInScope -> NamesInScope) -> (NameSpaceId -> ModulesInScope -> ModulesInScope -> ModulesInScope) -> Scope -> Scope -> Scope -- | Same as zipScope but applies the same function to both the -- public and private name spaces. zipScope_ :: (NamesInScope -> NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope -> ModulesInScope) -> Scope -> Scope -> Scope -- | Filter a scope keeping only concrete names matching the predicates. -- The first predicate is applied to the names and the second to the -- modules. filterScope :: (Name -> Bool) -> (Name -> Bool) -> Scope -> Scope -- | Return all names in a scope. allNamesInScope :: InScope a => Scope -> ThingsInScope a allNamesInScope' :: InScope a => Scope -> ThingsInScope (a, Access) -- | Returns the scope's non-private names. exportedNamesInScope :: InScope a => Scope -> ThingsInScope a namesInScope :: InScope a => [NameSpaceId] -> Scope -> ThingsInScope a allThingsInScope :: Scope -> NameSpace thingsInScope :: [NameSpaceId] -> Scope -> NameSpace -- | Merge two scopes. The result has the name of the first scope. mergeScope :: Scope -> Scope -> Scope -- | Merge a non-empty list of scopes. The result has the name of the first -- scope in the list. mergeScopes :: [Scope] -> Scope -- | Move all names in a scope to the given name space (except never move -- from Imported to Public). setScopeAccess :: NameSpaceId -> Scope -> Scope -- | Update a particular name space. setNameSpace :: NameSpaceId -> NameSpace -> Scope -> Scope -- | Modify a particular name space. modifyNameSpace :: NameSpaceId -> (NameSpace -> NameSpace) -> Scope -> Scope -- | Add names to a scope. addNamesToScope :: NameSpaceId -> Name -> [AbstractName] -> Scope -> Scope -- | Add a name to a scope. addNameToScope :: NameSpaceId -> Name -> AbstractName -> Scope -> Scope -- | Remove a name from a scope. removeNameFromScope :: NameSpaceId -> Name -> Scope -> Scope -- | Add a module to a scope. addModuleToScope :: NameSpaceId -> Name -> AbstractModule -> Scope -> Scope -- | Apply an ImportDirective to a scope. applyImportDirective :: ImportDirective -> Scope -> Scope -- | Rename the abstract names in a scope. renameCanonicalNames :: Map QName QName -> Map ModuleName ModuleName -> Scope -> Scope -- | Remove private name space of a scope. -- -- Should be a right identity for exportedNamesInScope. -- exportedNamesInScope . restrictPrivate == -- exportedNamesInScope. restrictPrivate :: Scope -> Scope -- | Remove names that can only be used qualified (when opening a scope) removeOnlyQualified :: Scope -> Scope -- | Add an explanation to why things are in scope. inScopeBecause :: (WhyInScope -> WhyInScope) -> Scope -> Scope -- | Get the public parts of the public modules of a scope publicModules :: ScopeInfo -> Map ModuleName Scope everythingInScope :: ScopeInfo -> NameSpace -- | Compute a flattened scope. Only include unqualified names or names -- qualified by modules in the first argument. flattenScope :: [[Name]] -> ScopeInfo -> Map QName [AbstractName] -- | Look up a name in the scope scopeLookup :: InScope a => QName -> ScopeInfo -> [a] scopeLookup' :: InScope a => QName -> ScopeInfo -> [(a, Access)] data AllowAmbiguousConstructors AllowAmbiguousConstructors :: AllowAmbiguousConstructors NoAmbiguousConstructors :: AllowAmbiguousConstructors -- | Find the concrete names that map (uniquely) to a given abstract name. -- Sort by length, shortest first. inverseScopeLookup :: Either ModuleName QName -> ScopeInfo -> [QName] inverseScopeLookup' :: AllowAmbiguousConstructors -> Either ModuleName QName -> ScopeInfo -> [QName] -- | Find the concrete names that map (uniquely) to a given abstract -- qualified name. Sort by length, shortest first. inverseScopeLookupName :: QName -> ScopeInfo -> [QName] inverseScopeLookupName' :: AllowAmbiguousConstructors -> QName -> ScopeInfo -> [QName] -- | Find the concrete names that map (uniquely) to a given abstract module -- name. Sort by length, shortest first. inverseScopeLookupModule :: ModuleName -> ScopeInfo -> [QName] -- | Add first string only if list is non-empty. blockOfLines :: String -> [String] -> [String] instance GHC.Classes.Eq Agda.Syntax.Scope.Base.AllowAmbiguousConstructors instance GHC.Enum.Bounded Agda.Syntax.Scope.Base.KindOfName instance GHC.Enum.Enum Agda.Syntax.Scope.Base.KindOfName instance GHC.Show.Show Agda.Syntax.Scope.Base.KindOfName instance GHC.Classes.Eq Agda.Syntax.Scope.Base.KindOfName instance GHC.Enum.Enum Agda.Syntax.Scope.Base.NameSpaceId instance GHC.Enum.Bounded Agda.Syntax.Scope.Base.NameSpaceId instance GHC.Classes.Eq Agda.Syntax.Scope.Base.NameSpaceId instance Control.DeepSeq.NFData Agda.Syntax.Scope.Base.LocalVar instance GHC.Classes.Eq Agda.Syntax.Scope.Base.LocalVar instance GHC.Classes.Ord Agda.Syntax.Scope.Base.LocalVar instance GHC.Show.Show Agda.Syntax.Scope.Base.LocalVar instance Agda.Syntax.Scope.Base.InScope Agda.Syntax.Scope.Base.AbstractName instance Agda.Syntax.Scope.Base.InScope Agda.Syntax.Scope.Base.AbstractModule instance GHC.Classes.Eq Agda.Syntax.Scope.Base.AbstractName instance GHC.Classes.Ord Agda.Syntax.Scope.Base.AbstractName instance GHC.Classes.Eq Agda.Syntax.Scope.Base.AbstractModule instance GHC.Classes.Ord Agda.Syntax.Scope.Base.AbstractModule instance GHC.Show.Show Agda.Syntax.Scope.Base.AbstractName instance GHC.Show.Show Agda.Syntax.Scope.Base.AbstractModule instance GHC.Show.Show Agda.Syntax.Scope.Base.NameSpaceId instance GHC.Show.Show Agda.Syntax.Scope.Base.NameSpace instance GHC.Show.Show Agda.Syntax.Scope.Base.Scope instance GHC.Show.Show Agda.Syntax.Scope.Base.ScopeInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Scope.Base.ScopeInfo instance Agda.Syntax.Position.HasRange Agda.Syntax.Scope.Base.AbstractName instance Agda.Syntax.Position.SetRange Agda.Syntax.Scope.Base.AbstractName -- | Utilities related to Geniplate. module Agda.Utils.Geniplate -- | A localised instance of instanceUniverseBiT. The generated -- universeBi functions neither descend into the types in -- dontDescendInto, nor into the types in the list argument. instanceUniverseBiT' :: [TypeQ] -> TypeQ -> Q [Dec] -- | A localised instance of instanceTransformBiMT. The generated -- transformBiM functions neither descend into the types in -- dontDescendInto, nor into the types in the list argument. instanceTransformBiMT' :: [TypeQ] -> TypeQ -> TypeQ -> Q [Dec] -- | Types which Geniplate should not descend into. dontDescendInto :: [TypeQ] -- | Types used for precise syntax highlighting. module Agda.Interaction.Highlighting.Precise -- | Syntactic aspects of the code. (These cannot overlap.) They can be -- obtained from the lexed tokens already, except for the -- NameKind. data Aspect Comment :: Aspect Keyword :: Aspect String :: Aspect Number :: Aspect -- | Symbols like forall, =, ->, etc. Symbol :: Aspect -- | Things like Set and Prop. PrimitiveType :: Aspect -- | Is the name an operator part? Name :: (Maybe NameKind) -> Bool -> Aspect -- | NameKinds are figured our during scope checking. data NameKind -- | Bound variable. Bound :: NameKind -- | Inductive or coinductive constructor. Constructor :: Induction -> NameKind Datatype :: NameKind -- | Record field. Field :: NameKind Function :: NameKind -- | Module name. Module :: NameKind Postulate :: NameKind -- | Primitive. Primitive :: NameKind -- | Record type. Record :: NameKind -- | Named argument, like x in {x = v} Argument :: NameKind -- | Other aspects, generated by type checking. (These can overlap with -- each other and with Aspects.) data OtherAspect Error :: OtherAspect DottedPattern :: OtherAspect UnsolvedMeta :: OtherAspect -- | Unsolved constraint not connected to meta-variable. This could for -- instance be an emptyness constraint. UnsolvedConstraint :: OtherAspect TerminationProblem :: OtherAspect -- | When this constructor is used it is probably a good idea to include a -- note explaining why the pattern is incomplete. IncompletePattern :: OtherAspect -- | Code which is being type-checked. TypeChecks :: OtherAspect -- | Meta information which can be associated with a character/character -- range. data Aspects Aspects :: Maybe Aspect -> [OtherAspect] -> Maybe String -> Maybe (TopLevelModuleName, Int) -> Aspects [aspect] :: Aspects -> Maybe Aspect [otherAspects] :: Aspects -> [OtherAspect] -- | This note, if present, can be displayed as a tool-tip or something -- like that. It should contain useful information about the range (like -- the module containing a certain identifier, or the fixity of an -- operator). [note] :: Aspects -> Maybe String -- | The definition site of the annotated thing, if applicable and known. -- File positions are counted from 1. [definitionSite] :: Aspects -> Maybe (TopLevelModuleName, Int) -- | A File is a mapping from file positions to meta information. -- -- The first position in the file has number 1. data File -- | Syntax highlighting information. type HighlightingInfo = CompressedFile -- | singleton rs m is a file whose positions are those in -- rs, and in which every position is associated with -- m. singleton :: Ranges -> Aspects -> File -- | Like singleton, but with several Ranges instead of only -- one. several :: [Ranges] -> Aspects -> File -- | Returns the smallest position, if any, in the File. smallestPos :: File -> Maybe Int -- | Convert the File to a map from file positions (counting from 1) -- to meta information. toMap :: File -> IntMap Aspects -- | A compressed File, in which consecutive positions with the same -- Aspects are stored together. newtype CompressedFile CompressedFile :: [(Range, Aspects)] -> CompressedFile [ranges] :: CompressedFile -> [(Range, Aspects)] -- | Invariant for compressed files. -- -- Note that these files are not required to be maximally -- compressed, because ranges are allowed to be empty, and the -- Aspectss in adjacent ranges are allowed to be equal. compressedFileInvariant :: CompressedFile -> Bool -- | Compresses a file by merging consecutive positions with equal meta -- information into longer ranges. compress :: File -> CompressedFile -- | Decompresses a compressed file. decompress :: CompressedFile -> File -- | Clear any highlighting info for the given ranges. Used to make sure -- unsolved meta highlighting overrides error highlighting. noHighlightingInRange :: Ranges -> CompressedFile -> CompressedFile -- | singletonC rs m is a file whose positions are those in -- rs, and in which every position is associated with -- m. singletonC :: Ranges -> Aspects -> CompressedFile -- | Like singletonR, but with a list of Ranges instead of -- a single one. severalC :: [Ranges] -> Aspects -> CompressedFile -- | splitAtC p f splits the compressed file f into -- (f1, f2), where all the positions in f1 are < -- p, and all the positions in f2 are >= p. splitAtC :: Int -> CompressedFile -> (CompressedFile, CompressedFile) -- | Returns the smallest position, if any, in the CompressedFile. smallestPosC :: CompressedFile -> Maybe Int -- | All the properties. tests :: IO Bool instance GHC.Show.Show Agda.Interaction.Highlighting.Precise.CompressedFile instance GHC.Classes.Eq Agda.Interaction.Highlighting.Precise.CompressedFile instance GHC.Show.Show Agda.Interaction.Highlighting.Precise.File instance GHC.Classes.Eq Agda.Interaction.Highlighting.Precise.File instance GHC.Show.Show Agda.Interaction.Highlighting.Precise.Aspects instance GHC.Classes.Eq Agda.Interaction.Highlighting.Precise.Aspects instance GHC.Enum.Bounded Agda.Interaction.Highlighting.Precise.OtherAspect instance GHC.Enum.Enum Agda.Interaction.Highlighting.Precise.OtherAspect instance GHC.Show.Show Agda.Interaction.Highlighting.Precise.OtherAspect instance GHC.Classes.Eq Agda.Interaction.Highlighting.Precise.OtherAspect instance GHC.Show.Show Agda.Interaction.Highlighting.Precise.Aspect instance GHC.Classes.Eq Agda.Interaction.Highlighting.Precise.Aspect instance GHC.Show.Show Agda.Interaction.Highlighting.Precise.NameKind instance GHC.Classes.Eq Agda.Interaction.Highlighting.Precise.NameKind instance GHC.Base.Monoid Agda.Interaction.Highlighting.Precise.Aspects instance GHC.Base.Monoid Agda.Interaction.Highlighting.Precise.File instance GHC.Base.Monoid Agda.Interaction.Highlighting.Precise.CompressedFile instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Interaction.Highlighting.Precise.Aspect instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Interaction.Highlighting.Precise.Aspect instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Interaction.Highlighting.Precise.NameKind instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Interaction.Highlighting.Precise.NameKind instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Interaction.Highlighting.Precise.OtherAspect instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Interaction.Highlighting.Precise.OtherAspect instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Interaction.Highlighting.Precise.Aspects instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Interaction.Highlighting.Precise.Aspects instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Interaction.Highlighting.Precise.File instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.Interaction.Highlighting.Precise.File instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Interaction.Highlighting.Precise.CompressedFile -- | Data type for all interactive responses module Agda.Interaction.Response -- | Responses for any interactive interface -- -- Note that the response is given in pieces and incrementally, so the -- user can have timely response even during long computations. data Response Resp_HighlightingInfo :: HighlightingInfo -> ModuleToSource -> Response Resp_Status :: Status -> Response Resp_JumpToError :: FilePath -> Int32 -> Response Resp_InteractionPoints :: [InteractionId] -> Response Resp_GiveAction :: InteractionId -> GiveResult -> Response Resp_MakeCase :: MakeCaseVariant -> [String] -> Response Resp_SolveAll :: [(InteractionId, Expr)] -> Response Resp_DisplayInfo :: DisplayInfo -> Response -- | The integer is the message's debug level. Resp_RunningInfo :: Int -> String -> Response Resp_ClearRunningInfo :: Response Resp_ClearHighlighting :: Response -- | There are two kinds of "make case" commands. data MakeCaseVariant Function :: MakeCaseVariant ExtendedLambda :: MakeCaseVariant -- | Info to display at the end of an interactive command data DisplayInfo Info_CompilationOk :: DisplayInfo Info_Constraints :: String -> DisplayInfo Info_AllGoals :: String -> DisplayInfo -- | When an error message is displayed this constructor should be used, if -- appropriate. Info_Error :: String -> DisplayInfo -- | Info_Intro denotes two different types of errors TODO: split -- these into separate constructors Info_Intro :: Doc -> DisplayInfo -- | Info_Auto denotes either an error or a success (when -- Resp_GiveAction is present) TODO: split these into separate -- constructors Info_Auto :: String -> DisplayInfo Info_ModuleContents :: Doc -> DisplayInfo Info_WhyInScope :: Doc -> DisplayInfo Info_NormalForm :: Doc -> DisplayInfo Info_GoalType :: Doc -> DisplayInfo Info_CurrentGoal :: Doc -> DisplayInfo Info_InferredType :: Doc -> DisplayInfo Info_Context :: Doc -> DisplayInfo Info_HelperFunction :: Doc -> DisplayInfo Info_Version :: DisplayInfo -- | Status information. data Status Status :: Bool -> Bool -> Status -- | Are implicit arguments displayed? [sShowImplicitArguments] :: Status -> Bool -- | Has the module been successfully type checked? [sChecked] :: Status -> Bool -- | Give action result -- -- Comment derived from agda2-mode.el -- -- If GiveResult is 'Give_String s', then the goal is replaced by -- s, and otherwise the text inside the goal is retained -- (parenthesised if GiveResult is Give_Paren). data GiveResult Give_String :: String -> GiveResult Give_Paren :: GiveResult Give_NoParen :: GiveResult -- | Callback fuction to call when there is a response to give to the -- interactive frontend. -- -- Note that the response is given in pieces and incrementally, so the -- user can have timely response even during long computations. -- -- Typical InteractionOutputCallback functions: -- -- type InteractionOutputCallback = Response -> TCM () -- | The default InteractionOutputCallback function prints certain -- things to stdout (other things generate internal errors). defaultInteractionOutputCallback :: InteractionOutputCallback instance GHC.Show.Show Agda.Interaction.Response.DisplayInfo -- | Generic traversal and reduce for concrete syntax, in the style of -- Agda.Syntax.Internal.Generic. -- -- However, here we use the terminology of Traversable. module Agda.Syntax.Concrete.Generic -- | Generic traversals for concrete expressions. -- -- Note: does not go into patterns! class ExprLike a where traverseExpr = (throwImpossible (Impossible "src/full/Agda/Syntax/Concrete/Generic.hs" 34)) foldExpr = (throwImpossible (Impossible "src/full/Agda/Syntax/Concrete/Generic.hs" 35)) -- | This corresponds to map. mapExpr :: ExprLike a => (Expr -> Expr) -> a -> a -- | This corresponds to mapM. traverseExpr :: (ExprLike a, Monad m, Applicative m) => (Expr -> m Expr) -> a -> m a -- | This is a reduce. foldExpr :: (ExprLike a, Monoid m) => (Expr -> m) -> a -> m instance Agda.Syntax.Concrete.Generic.ExprLike Agda.Syntax.Concrete.Name.Name instance Agda.Syntax.Concrete.Generic.ExprLike Agda.Syntax.Concrete.Name.QName instance Agda.Syntax.Concrete.Generic.ExprLike a => Agda.Syntax.Concrete.Generic.ExprLike (Agda.Syntax.Common.Named name a) instance Agda.Syntax.Concrete.Generic.ExprLike a => Agda.Syntax.Concrete.Generic.ExprLike (Agda.Syntax.Concrete.Arg a) instance Agda.Syntax.Concrete.Generic.ExprLike a => Agda.Syntax.Concrete.Generic.ExprLike [a] instance Agda.Syntax.Concrete.Generic.ExprLike a => Agda.Syntax.Concrete.Generic.ExprLike (GHC.Base.Maybe a) instance Agda.Syntax.Concrete.Generic.ExprLike a => Agda.Syntax.Concrete.Generic.ExprLike (Agda.Syntax.Concrete.TypedBinding' a) instance Agda.Syntax.Concrete.Generic.ExprLike a => Agda.Syntax.Concrete.Generic.ExprLike (Agda.Syntax.Concrete.RHS' a) instance Agda.Syntax.Concrete.Generic.ExprLike a => Agda.Syntax.Concrete.Generic.ExprLike (Agda.Syntax.Concrete.WhereClause' a) instance (Agda.Syntax.Concrete.Generic.ExprLike a, Agda.Syntax.Concrete.Generic.ExprLike b) => Agda.Syntax.Concrete.Generic.ExprLike (a, b) instance (Agda.Syntax.Concrete.Generic.ExprLike a, Agda.Syntax.Concrete.Generic.ExprLike b, Agda.Syntax.Concrete.Generic.ExprLike c) => Agda.Syntax.Concrete.Generic.ExprLike (a, b, c) instance Agda.Syntax.Concrete.Generic.ExprLike Agda.Syntax.Concrete.Expr instance Agda.Syntax.Concrete.Generic.ExprLike a => Agda.Syntax.Concrete.Generic.ExprLike (Agda.Syntax.Concrete.OpApp a) instance Agda.Syntax.Concrete.Generic.ExprLike Agda.Syntax.Concrete.LamBinding instance Agda.Syntax.Concrete.Generic.ExprLike Agda.Syntax.Concrete.TypedBindings instance Agda.Syntax.Concrete.Generic.ExprLike Agda.Syntax.Concrete.LHS instance Agda.Syntax.Concrete.Generic.ExprLike Agda.Syntax.Concrete.ModuleApplication instance Agda.Syntax.Concrete.Generic.ExprLike Agda.Syntax.Concrete.Declaration -- | An info object contains additional information about a piece of -- abstract syntax that isn't part of the actual syntax. For instance, it -- might contain the source code position of an expression or the -- concrete syntax that an internal expression originates from. module Agda.Syntax.Info data MetaInfo MetaInfo :: Range -> ScopeInfo -> Maybe MetaId -> String -> MetaInfo [metaRange] :: MetaInfo -> Range [metaScope] :: MetaInfo -> ScopeInfo [metaNumber] :: MetaInfo -> Maybe MetaId [metaNameSuggestion] :: MetaInfo -> String emptyMetaInfo :: MetaInfo newtype ExprInfo ExprRange :: Range -> ExprInfo exprNoRange :: ExprInfo data ModuleInfo ModuleInfo :: Range -> Range -> Maybe Name -> Maybe OpenShortHand -> Maybe ImportDirective -> ModuleInfo [minfoRange] :: ModuleInfo -> Range -- | The range of the "as" and "to" keywords, if any. Retained for -- highlighting purposes. [minfoAsTo] :: ModuleInfo -> Range -- | The "as" module name, if any. Retained for highlighting purposes. [minfoAsName] :: ModuleInfo -> Maybe Name [minfoOpenShort] :: ModuleInfo -> Maybe OpenShortHand -- | Retained for abstractToConcrete of ModuleMacro. [minfoDirective] :: ModuleInfo -> Maybe ImportDirective newtype LetInfo LetRange :: Range -> LetInfo data DefInfo DefInfo :: Fixity' -> Access -> IsAbstract -> IsInstance -> DeclInfo -> DefInfo [defFixity] :: DefInfo -> Fixity' [defAccess] :: DefInfo -> Access [defAbstract] :: DefInfo -> IsAbstract [defInstance] :: DefInfo -> IsInstance [defInfo] :: DefInfo -> DeclInfo mkDefInfo :: Name -> Fixity' -> Access -> IsAbstract -> Range -> DefInfo -- | Same as mkDefInfo but where we can also give the -- IsInstance mkDefInfoInstance :: Name -> Fixity' -> Access -> IsAbstract -> IsInstance -> Range -> DefInfo data DeclInfo DeclInfo :: Name -> Range -> DeclInfo [declName] :: DeclInfo -> Name [declRange] :: DeclInfo -> Range data MutualInfo MutualInfo :: TerminationCheck Name -> Range -> MutualInfo [mutualTermCheck] :: MutualInfo -> TerminationCheck Name [mutualRange] :: MutualInfo -> Range newtype LHSInfo LHSRange :: Range -> LHSInfo -- | For a general pattern we remember the source code position. newtype PatInfo PatRange :: Range -> PatInfo -- | Empty range for patterns. patNoRange :: PatInfo -- | Constructor pattern info. data ConPatInfo ConPatInfo :: ConPOrigin -> PatInfo -> ConPatInfo -- | Does this pattern come form the eta-expansion of an implicit pattern? [patOrigin] :: ConPatInfo -> ConPOrigin [patInfo] :: ConPatInfo -> PatInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Info.PatInfo instance Agda.Syntax.Position.HasRange Agda.Syntax.Info.PatInfo instance GHC.Show.Show Agda.Syntax.Info.PatInfo instance Agda.Utils.Null.Null Agda.Syntax.Info.PatInfo instance GHC.Classes.Eq Agda.Syntax.Info.PatInfo instance Agda.Utils.Null.Null Agda.Syntax.Info.LHSInfo instance GHC.Show.Show Agda.Syntax.Info.LHSInfo instance GHC.Show.Show Agda.Syntax.Info.MutualInfo instance GHC.Show.Show Agda.Syntax.Info.DefInfo instance GHC.Show.Show Agda.Syntax.Info.DeclInfo instance Agda.Utils.Null.Null Agda.Syntax.Info.LetInfo instance GHC.Show.Show Agda.Syntax.Info.LetInfo instance Agda.Utils.Null.Null Agda.Syntax.Info.ExprInfo instance GHC.Show.Show Agda.Syntax.Info.ExprInfo instance GHC.Show.Show Agda.Syntax.Info.MetaInfo instance (GHC.Show.Show Agda.Syntax.Concrete.OpenShortHand, GHC.Show.Show Agda.Syntax.Concrete.ImportDirective) => GHC.Show.Show Agda.Syntax.Info.ModuleInfo instance Agda.Syntax.Position.HasRange Agda.Syntax.Info.MetaInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Info.MetaInfo instance Agda.Syntax.Position.HasRange Agda.Syntax.Info.ExprInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Info.ExprInfo instance Agda.Syntax.Position.HasRange Agda.Syntax.Info.ModuleInfo instance Agda.Syntax.Position.SetRange Agda.Syntax.Info.ModuleInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Info.ModuleInfo instance Agda.Syntax.Position.HasRange Agda.Syntax.Info.LetInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Info.LetInfo instance Agda.Syntax.Position.HasRange Agda.Syntax.Info.DefInfo instance Agda.Syntax.Position.SetRange Agda.Syntax.Info.DefInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Info.DefInfo instance Agda.Syntax.Position.HasRange Agda.Syntax.Info.DeclInfo instance Agda.Syntax.Position.SetRange Agda.Syntax.Info.DeclInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Info.DeclInfo instance Agda.Syntax.Position.HasRange Agda.Syntax.Info.MutualInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Info.MutualInfo instance Agda.Syntax.Position.HasRange Agda.Syntax.Info.LHSInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Info.LHSInfo instance GHC.Show.Show Agda.Syntax.Info.ConPatInfo instance Agda.Syntax.Position.HasRange Agda.Syntax.Info.ConPatInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Info.ConPatInfo instance Agda.Syntax.Position.SetRange Agda.Syntax.Info.ConPatInfo -- | Pretty printer for the concrete syntax. module Agda.Syntax.Concrete.Pretty braces' :: Doc -> Doc dbraces :: Doc -> Doc bracesAndSemicolons :: [Doc] -> Doc arrow :: Doc lambda :: Doc -- | prettyHiding info visible doc puts the correct braces around -- doc according to info info and returns visible -- doc if the we deal with a visible thing. prettyHiding :: LensHiding a => a -> (Doc -> Doc) -> Doc -> Doc prettyRelevance :: LensRelevance a => a -> Doc -> Doc newtype Tel Tel :: Telescope -> Tel pColors :: String -> [Color] -> Doc smashTel :: Telescope -> Telescope prettyOpApp :: Pretty a => QName -> [a] -> [Doc] instance GHC.Show.Show Agda.Syntax.Concrete.Expr instance GHC.Show.Show Agda.Syntax.Concrete.Declaration instance GHC.Show.Show Agda.Syntax.Concrete.Pattern instance GHC.Show.Show Agda.Syntax.Concrete.TypedBinding instance GHC.Show.Show Agda.Syntax.Concrete.TypedBindings instance GHC.Show.Show Agda.Syntax.Concrete.LamBinding instance GHC.Show.Show Agda.Syntax.Concrete.ImportDirective instance GHC.Show.Show Agda.Syntax.Concrete.Pragma instance GHC.Show.Show Agda.Syntax.Concrete.RHS instance (Agda.Utils.Pretty.Pretty a, Agda.Utils.Pretty.Pretty b) => Agda.Utils.Pretty.Pretty (a, b) instance Agda.Utils.Pretty.Pretty (Agda.Syntax.Fixity.ThingWithFixity Agda.Syntax.Concrete.Name.Name) instance Agda.Utils.Pretty.Pretty a => Agda.Utils.Pretty.Pretty (Agda.Syntax.Common.WithHiding a) instance Agda.Utils.Pretty.Pretty Agda.Syntax.Common.Relevance instance Agda.Utils.Pretty.Pretty Agda.Syntax.Common.Induction instance Agda.Utils.Pretty.Pretty (Agda.Syntax.Concrete.OpApp Agda.Syntax.Concrete.Expr) instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.Expr instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.BoundName instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.LamBinding instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.TypedBindings instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.Pretty.Tel instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.ColoredTypedBinding instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.TypedBinding instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.RHS instance GHC.Show.Show Agda.Syntax.Concrete.WhereClause instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.WhereClause instance GHC.Show.Show Agda.Syntax.Concrete.LHS instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.LHS instance GHC.Show.Show Agda.Syntax.Concrete.LHSCore instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.LHSCore instance Agda.Utils.Pretty.Pretty [Agda.Syntax.Concrete.Declaration] instance GHC.Show.Show Agda.Syntax.Concrete.ModuleApplication instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.ModuleApplication instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.Declaration instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.OpenShortHand instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.Pragma instance Agda.Utils.Pretty.Pretty Agda.Syntax.Fixity.Fixity instance Agda.Utils.Pretty.Pretty Agda.Syntax.Notation.GenPart instance Agda.Utils.Pretty.Pretty Agda.Syntax.Notation.Notation instance Agda.Utils.Pretty.Pretty Agda.Syntax.Fixity.Fixity' instance Agda.Utils.Pretty.Pretty e => Agda.Utils.Pretty.Pretty (Agda.Syntax.Concrete.Arg e) instance Agda.Utils.Pretty.Pretty e => Agda.Utils.Pretty.Pretty (Agda.Syntax.Common.Named_ e) instance Agda.Utils.Pretty.Pretty [Agda.Syntax.Concrete.Pattern] instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.Pattern instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.ImportDirective instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.UsingOrHiding instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.ImportedName -- | Preprocess Declarations, producing NiceDeclarations. -- -- module Agda.Syntax.Concrete.Definitions -- | The nice declarations. No fixity declarations and function definitions -- are contained in a single constructor instead of spread out between -- type signatures and clauses. The private, postulate, -- abstract and instance modifiers have been -- distributed to the individual declarations. data NiceDeclaration -- | Axioms and functions can be declared irrelevant. (Hiding should be -- NotHidden) Axiom :: Range -> Fixity' -> Access -> IsInstance -> ArgInfo -> Name -> Expr -> NiceDeclaration NiceField :: Range -> Fixity' -> Access -> IsAbstract -> Name -> (Arg Expr) -> NiceDeclaration PrimitiveFunction :: Range -> Fixity' -> Access -> IsAbstract -> Name -> Expr -> NiceDeclaration NiceMutual :: Range -> TerminationCheck -> [NiceDeclaration] -> NiceDeclaration NiceModule :: Range -> Access -> IsAbstract -> QName -> Telescope -> [Declaration] -> NiceDeclaration NiceModuleMacro :: Range -> Access -> Name -> ModuleApplication -> OpenShortHand -> ImportDirective -> NiceDeclaration NiceOpen :: Range -> QName -> ImportDirective -> NiceDeclaration NiceImport :: Range -> QName -> (Maybe AsName) -> OpenShortHand -> ImportDirective -> NiceDeclaration NicePragma :: Range -> Pragma -> NiceDeclaration NiceRecSig :: Range -> Fixity' -> Access -> Name -> [LamBinding] -> Expr -> NiceDeclaration NiceDataSig :: Range -> Fixity' -> Access -> Name -> [LamBinding] -> Expr -> NiceDeclaration -- | An uncategorized function clause, could be a function clause without -- type signature or a pattern lhs (e.g. for irrefutable let). The -- Declaration is the actual FunClause. NiceFunClause :: Range -> Access -> IsAbstract -> TerminationCheck -> Declaration -> NiceDeclaration FunSig :: Range -> Fixity' -> Access -> IsInstance -> ArgInfo -> TerminationCheck -> Name -> Expr -> NiceDeclaration -- | Block of function clauses (we have seen the type signature before). -- The Declarations are the original declarations that were -- processed into this FunDef and are only used in -- notSoNiceDeclaration. FunDef :: Range -> [Declaration] -> Fixity' -> IsAbstract -> TerminationCheck -> Name -> [Clause] -> NiceDeclaration DataDef :: Range -> Fixity' -> IsAbstract -> Name -> [LamBinding] -> [NiceConstructor] -> NiceDeclaration RecDef :: Range -> Fixity' -> IsAbstract -> Name -> (Maybe (Ranged Induction)) -> (Maybe (ThingWithFixity Name)) -> [LamBinding] -> [NiceDeclaration] -> NiceDeclaration NicePatternSyn :: Range -> Fixity' -> Name -> [Arg Name] -> Pattern -> NiceDeclaration NiceUnquoteDecl :: Range -> Fixity' -> Access -> IsInstance -> IsAbstract -> TerminationCheck -> Name -> Expr -> NiceDeclaration -- | Only Axioms. type NiceConstructor = NiceTypeSignature -- | Only Axioms. type NiceTypeSignature = NiceDeclaration -- | One clause in a function definition. There is no guarantee that the -- LHS actually declares the Name. We will have to check -- that later. data Clause Clause :: Name -> LHS -> RHS -> WhereClause -> [Clause] -> Clause -- | The exception type. data DeclarationException MultipleFixityDecls :: [(Name, [Fixity'])] -> DeclarationException InvalidName :: Name -> DeclarationException DuplicateDefinition :: Name -> DeclarationException MissingDefinition :: Name -> DeclarationException MissingWithClauses :: Name -> DeclarationException MissingTypeSignature :: LHS -> DeclarationException MissingDataSignature :: Name -> DeclarationException WrongDefinition :: Name -> DataRecOrFun -> DataRecOrFun -> DeclarationException WrongParameters :: Name -> DeclarationException NotAllowedInMutual :: NiceDeclaration -> DeclarationException UnknownNamesInFixityDecl :: [Name] -> DeclarationException Codata :: Range -> DeclarationException DeclarationPanic :: String -> DeclarationException UselessPrivate :: Range -> DeclarationException UselessAbstract :: Range -> DeclarationException UselessInstance :: Range -> DeclarationException WrongContentBlock :: KindOfBlock -> Range -> DeclarationException -- | in a mutual block, a clause could belong to any of the [Name] -- type signatures AmbiguousFunClauses :: LHS -> [Name] -> DeclarationException InvalidTerminationCheckPragma :: Range -> DeclarationException -- | In a mutual block, all or none need a MEASURE pragma. Range is of -- mutual block. InvalidMeasureMutual :: Range -> DeclarationException -- | Pragma {--} has been replaced by {--} and {--}. PragmaNoTerminationCheck :: Range -> DeclarationException -- | Nicifier monad. type Nice = StateT NiceEnv (Either DeclarationException) runNice :: Nice a -> Either DeclarationException a -- | Main. niceDeclarations :: [Declaration] -> Nice [NiceDeclaration] -- | (Approximately) convert a NiceDeclaration back to a -- Declaration. notSoNiceDeclaration :: NiceDeclaration -> Declaration -- | Has the NiceDeclaration a field of type IsAbstract? niceHasAbstract :: NiceDeclaration -> Maybe IsAbstract -- | Termination measure is, for now, a variable name. type Measure = Name instance GHC.Show.Show Agda.Syntax.Concrete.Definitions.DeclKind instance GHC.Classes.Eq Agda.Syntax.Concrete.Definitions.DeclKind instance GHC.Classes.Eq Agda.Syntax.Concrete.Definitions.DataRecOrFun instance GHC.Show.Show Agda.Syntax.Concrete.Definitions.InMutual instance GHC.Classes.Eq Agda.Syntax.Concrete.Definitions.InMutual instance GHC.Show.Show Agda.Syntax.Concrete.Definitions.KindOfBlock instance GHC.Classes.Ord Agda.Syntax.Concrete.Definitions.KindOfBlock instance GHC.Classes.Eq Agda.Syntax.Concrete.Definitions.KindOfBlock instance GHC.Show.Show Agda.Syntax.Concrete.Definitions.NiceDeclaration instance GHC.Show.Show Agda.Syntax.Concrete.Definitions.Clause instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.Definitions.DeclarationException instance Agda.Syntax.Position.HasRange Agda.Syntax.Concrete.Definitions.NiceDeclaration instance Agda.Utils.Except.Error Agda.Syntax.Concrete.Definitions.DeclarationException instance Agda.Utils.Pretty.Pretty Agda.Syntax.Concrete.Definitions.DeclarationException instance GHC.Show.Show Agda.Syntax.Concrete.Definitions.DataRecOrFun instance GHC.Base.Monoid (Agda.Syntax.Concrete.Definitions.Nice Agda.Syntax.Concrete.Definitions.Fixities) module Agda.Syntax.Parser.Monad -- | The parse monad. Equivalent to StateT ParseState (Either -- ParseError) except for the definition of fail, -- which builds a suitable ParseError object. data Parser a -- | The result of parsing something. data ParseResult a ParseOk :: ParseState -> a -> ParseResult a ParseFailed :: ParseError -> ParseResult a -- | The parser state. Contains everything the parser and the lexer could -- ever need. data ParseState PState :: !Position -> !Position -> String -> !Char -> String -> [LayoutContext] -> [LexState] -> ParseFlags -> ParseState -- | position at current input location [parsePos] :: ParseState -> !Position -- | position of last token [parseLastPos] :: ParseState -> !Position -- | the current input [parseInp] :: ParseState -> String -- | the character before the input [parsePrevChar] :: ParseState -> !Char -- | the previous token [parsePrevToken] :: ParseState -> String -- | the stack of layout contexts [parseLayout] :: ParseState -> [LayoutContext] -- | the state of the lexer (states can be nested so we need a stack) [parseLexState] :: ParseState -> [LexState] -- | currently there are no flags [parseFlags] :: ParseState -> ParseFlags -- | What you get if parsing fails. data ParseError ParseError :: Position -> String -> String -> String -> ParseError -- | where the error occured [errPos] :: ParseError -> Position -- | the remaining input [errInput] :: ParseError -> String -- | the previous token [errPrevToken] :: ParseError -> String -- | hopefully an explanation of what happened [errMsg] :: ParseError -> String -- | To do context sensitive lexing alex provides what is called start -- codes in the Alex documentation. It is really an integer -- representing the state of the lexer, so we call it LexState -- instead. type LexState = Int -- | We need to keep track of the context to do layout. The context -- specifies the indentation (if any) of a layout block. See -- Agda.Syntax.Parser.Layout for more informaton. data LayoutContext -- | no layout NoLayout :: LayoutContext -- | layout at specified column Layout :: Int32 -> LayoutContext -- | There aren't any parser flags at the moment. data ParseFlags ParseFlags :: Bool -> ParseFlags -- | Should comment tokens be returned by the lexer? [parseKeepComments] :: ParseFlags -> Bool -- | Constructs the initial state of the parser. The string argument is the -- input string, the file path is only there because it's part of a -- position. initState :: Maybe AbsolutePath -> ParseFlags -> String -> [LexState] -> ParseState -- | The default flags. defaultParseFlags :: ParseFlags -- | The most general way of parsing a string. The -- Agda.Syntax.Parser will define more specialised functions that -- supply the ParseFlags and the LexState. parse :: ParseFlags -> [LexState] -> Parser a -> String -> ParseResult a -- | The even more general way of parsing a string. parsePosString :: Position -> ParseFlags -> [LexState] -> Parser a -> String -> ParseResult a -- | The most general way of parsing a file. The Agda.Syntax.Parser -- will define more specialised functions that supply the -- ParseFlags and the LexState. -- -- Note that Agda source files always use the UTF-8 character encoding. parseFile :: ParseFlags -> [LexState] -> Parser a -> AbsolutePath -> IO (ParseResult a) setParsePos :: Position -> Parser () setLastPos :: Position -> Parser () -- | The parse interval is between the last position and the current -- position. getParseInterval :: Parser Interval setPrevToken :: String -> Parser () getParseFlags :: Parser ParseFlags getLexState :: Parser [LexState] pushLexState :: LexState -> Parser () popLexState :: Parser () -- | Return the current layout context. topContext :: Parser LayoutContext popContext :: Parser () pushContext :: LayoutContext -> Parser () -- | Should only be used at the beginning of a file. When we start parsing -- we should be in layout mode. Instead of forcing zero indentation we -- use the indentation of the first token. pushCurrentContext :: Parser () -- |
--   parseError = fail
--   
parseError :: String -> Parser a -- | Fake a parse error at the specified position. Used, for instance, when -- lexing nested comments, which when failing will always fail at the end -- of the file. A more informative position is the beginning of the -- failing comment. parseErrorAt :: Position -> String -> Parser a -- | Use parseErrorAt or parseError as appropriate. parseError' :: Maybe Position -> String -> Parser a -- | For lexical errors we want to report the current position as the site -- of the error, whereas for parse errors the previous position is the -- one we're interested in (since this will be the position of the token -- we just lexed). This function does parseErrorAt the current -- position. lexError :: String -> Parser a instance GHC.Show.Show Agda.Syntax.Parser.Monad.ParseState instance GHC.Show.Show Agda.Syntax.Parser.Monad.ParseFlags instance GHC.Show.Show Agda.Syntax.Parser.Monad.LayoutContext instance GHC.Exception.Exception Agda.Syntax.Parser.Monad.ParseError instance GHC.Base.Monad Agda.Syntax.Parser.Monad.Parser instance GHC.Base.Functor Agda.Syntax.Parser.Monad.Parser instance GHC.Base.Applicative Agda.Syntax.Parser.Monad.Parser instance Control.Monad.Error.Class.MonadError Agda.Syntax.Parser.Monad.ParseError Agda.Syntax.Parser.Monad.Parser instance Control.Monad.State.Class.MonadState Agda.Syntax.Parser.Monad.ParseState Agda.Syntax.Parser.Monad.Parser instance GHC.Show.Show Agda.Syntax.Parser.Monad.ParseError instance Agda.Utils.Pretty.Pretty Agda.Syntax.Parser.Monad.ParseError instance Agda.Syntax.Position.HasRange Agda.Syntax.Parser.Monad.ParseError -- | This module defines the things required by Alex and some other Alex -- related things. module Agda.Syntax.Parser.Alex -- | This is what the lexer manipulates. data AlexInput AlexInput :: !Position -> String -> !Char -> AlexInput -- | current position [lexPos] :: AlexInput -> !Position -- | current input [lexInput] :: AlexInput -> String -- | previously read character [lexPrevChar] :: AlexInput -> !Char -- | A lens for lexInput. lensLexInput :: Lens' String AlexInput -- | Get the previously lexed character. Same as lexPrevChar. Alex -- needs this to be defined to handle "patterns with a left-context". alexInputPrevChar :: AlexInput -> Char -- | Lex a character. No surprises. -- -- This function is used by Alex 2. alexGetChar :: AlexInput -> Maybe (Char, AlexInput) -- | A variant of alexGetChar. -- -- This function is used by Alex 3. alexGetByte :: AlexInput -> Maybe (Word8, AlexInput) -- | In the lexer, regular expressions are associated with lex actions -- who's task it is to construct the tokens. type LexAction r = PreviousInput -> CurrentInput -> TokenLength -> Parser r -- | Sometimes regular expressions aren't enough. Alex provides a way to do -- arbitrary computations to see if the input matches. This is done with -- a lex predicate. type LexPredicate = ([LexState], ParseFlags) -> PreviousInput -> TokenLength -> CurrentInput -> Bool -- | Conjunction of LexPredicates. (.&&.) :: LexPredicate -> LexPredicate -> LexPredicate -- | Disjunction of LexPredicates. (.||.) :: LexPredicate -> LexPredicate -> LexPredicate -- | Negation of LexPredicates. not' :: LexPredicate -> LexPredicate type PreviousInput = AlexInput type CurrentInput = AlexInput type TokenLength = Int getLexInput :: Parser AlexInput setLexInput :: AlexInput -> Parser () -- | When lexing by hands (for instance string literals) we need to do some -- looking ahead. The LookAhead monad keeps track of the position -- we are currently looking at, and provides facilities to synchronise -- the look-ahead position with the actual position of the Parser -- monad (see sync and rollback). module Agda.Syntax.Parser.LookAhead -- | The LookAhead monad is basically a state monad keeping with an extra -- AlexInput, wrapped around the Parser monad. data LookAhead a -- | Run a LookAhead computation. The first argument is the error -- function. runLookAhead :: (forall b. String -> LookAhead b) -> LookAhead a -> Parser a -- | Get the current look-ahead position. getInput :: LookAhead AlexInput -- | Set the look-ahead position. setInput :: AlexInput -> LookAhead () -- | Lift a computation in the Parser monad to the LookAhead -- monad. liftP :: Parser a -> LookAhead a -- | Look at the next character. Fails if there are no more characters. nextChar :: LookAhead Char -- | Consume the next character. Does nextChar followed by -- sync. eatNextChar :: LookAhead Char -- | Consume all the characters up to the current look-ahead position. sync :: LookAhead () -- | Undo look-ahead. Restores the input from the ParseState. rollback :: LookAhead () -- | Do a case on the current input string. If any of the given strings -- match we move past it and execute the corresponding action. If no -- string matches, we execute a default action, advancing the input one -- character. This function only affects the look-ahead position. match :: [(String, LookAhead a)] -> LookAhead a -> LookAhead a -- | Same as match but takes the initial character from the first -- argument instead of reading it from the input. Consequently, in the -- default case the input is not advanced. match' :: Char -> [(String, LookAhead a)] -> LookAhead a -> LookAhead a instance GHC.Base.Applicative Agda.Syntax.Parser.LookAhead.LookAhead instance GHC.Base.Functor Agda.Syntax.Parser.LookAhead.LookAhead instance GHC.Base.Monad Agda.Syntax.Parser.LookAhead.LookAhead -- | This module defines the lex action to lex nested comments. As is -- well-known this cannot be done by regular expressions (which, -- incidently, is probably the reason why C-comments don't nest). -- -- When scanning nested comments we simply keep track of the nesting -- level, counting up for open comments and down for close -- comments. module Agda.Syntax.Parser.Comments -- | Should comment tokens be output? keepComments :: LexPredicate -- | Should comment tokens be output? keepCommentsM :: Parser Bool -- | Manually lexing a block comment. Assumes an open comment has -- been lexed. In the end the comment is discarded and lexToken is -- called to lex a real token. nestedComment :: LexAction Token -- | Lex a hole ({! ... !}). Holes can be nested. Returns -- TokSymbol SymQuestionMark. hole :: LexAction Token -- | Skip a block of text enclosed by the given open and close strings. -- Assumes the first open string has been consumed. Open-close pairs may -- be nested. skipBlock :: String -> String -> LookAhead () -- | The code to lex string and character literals. Basically the same code -- as in GHC. module Agda.Syntax.Parser.StringLiterals -- | Lex a string literal. Assumes that a double quote has been lexed. litString :: LexAction Token -- | Lex a character literal. Assumes that a single quote has been lexed. A -- character literal is lexed in exactly the same way as a string -- literal. Only before returning the token do we check that the lexed -- string is of length 1. This is maybe not the most efficient way of -- doing things, but on the other hand it will only be inefficient if -- there is a lexical error. litChar :: LexAction Token -- | The lexer is generated by Alex (http://www.haskell.org/alex) -- and is an adaptation of GHC's lexer. The main lexing function -- lexer is called by the Agda.Syntax.Parser.Parser to get -- the next token from the input. module Agda.Syntax.Parser.Lexer -- | Return the next token. This is the function used by Happy in the -- parser. -- --
--   lexer k = lexToken >>= k
--   
lexer :: (Token -> Parser a) -> Parser a -- | This is the initial state for parsing a regular, non-literate file. normal :: LexState -- | This is the initial state for parsing a literate file. Code blocks -- should be enclosed in \begin{code} \end{code} pairs. literate :: LexState code :: Int -- | The layout state. Entered when we see a layout keyword -- (withLayout) and exited either when seeing an open brace -- (openBrace) or at the next token (newLayoutContext). -- -- Update: we don't use braces for layout anymore. layout :: LexState -- | We enter this state from newLayoutContext when the token -- following a layout keyword is to the left of (or at the same column -- as) the current layout context. Example: -- --
--   data Empty : Set where
--   foo : Empty -> Nat
--   
-- -- Here the second line is not part of the where clause since it -- is has the same indentation as the data definition. What we -- have to do is insert an empty layout block {} after the -- where. The only thing that can happen in this state is that -- emptyLayout is executed, generating the closing brace. The open -- brace is generated when entering by newLayoutContext. empty_layout :: LexState -- | This state is entered at the beginning of each line. You can't lex -- anything in this state, and to exit you have to check the layout rule. -- Done with offsideRule. bol :: LexState -- | This state can only be entered by the parser. In this state you can -- only lex the keywords using, hiding, -- renaming and to. Moreover they are only keywords in -- this particular state. The lexer will never enter this state by -- itself, that has to be done in the parser. imp_dir :: LexState data AlexReturn a AlexEOF :: AlexReturn a AlexError :: !AlexInput -> AlexReturn a AlexSkip :: !AlexInput -> !Int -> AlexReturn a AlexToken :: !AlexInput -> !Int -> a -> AlexReturn a -- | This is the main lexing function generated by Alex. alexScanUser :: ([LexState], ParseFlags) -> AlexInput -> Int -> AlexReturn (LexAction Token) instance GHC.Base.Functor Agda.Syntax.Parser.Lexer.AlexLastAcc -- | This module contains the building blocks used to construct the lexer. module Agda.Syntax.Parser.LexActions -- | Scan the input to find the next token. Calls alexScanUser. This -- is the main lexing function where all the work happens. The function -- lexer, used by the parser is the continuation version of this -- function. lexToken :: Parser Token -- | The most general way of parsing a token. token :: (String -> Parser tok) -> LexAction tok -- | Parse a token from an Interval and the lexed string. withInterval :: ((Interval, String) -> tok) -> LexAction tok -- | Like withInterval, but applies a function to the string. withInterval' :: (String -> a) -> ((Interval, a) -> tok) -> LexAction tok -- | Return a token without looking at the lexed string. withInterval_ :: (Interval -> r) -> LexAction r -- | Executed for layout keywords. Enters the layout state and -- performs the given action. withLayout :: LexAction r -> LexAction r -- | Enter a new state without consuming any input. begin :: LexState -> LexAction Token -- | Exit the current state without consuming any input end :: LexAction Token -- | Exit the current state and perform the given action. endWith :: LexAction a -> LexAction a -- | Enter a new state throwing away the current lexeme. begin_ :: LexState -> LexAction Token -- | Exit the current state throwing away the current lexeme. end_ :: LexAction Token -- | For lexical errors we want to report the current position as the site -- of the error, whereas for parse errors the previous position is the -- one we're interested in (since this will be the position of the token -- we just lexed). This function does parseErrorAt the current -- position. lexError :: String -> Parser a -- | Parse a Keyword token, triggers layout for -- layoutKeywords. keyword :: Keyword -> LexAction Token -- | Parse a Symbol token. symbol :: Symbol -> LexAction Token -- | Parse an identifier. Identifiers can be qualified (see Name). -- Example: Foo.Bar.f identifier :: LexAction Token -- | Parse a literal. literal :: Read a => (Range -> a -> Literal) -> LexAction Token -- | True when the given character is the next character of the input -- string. followedBy :: Char -> LexPredicate -- | True if we are at the end of the file. eof :: LexPredicate -- | True if the given state appears somewhere on the state stack inState :: LexState -> LexPredicate -- | This module contains the lex actions that handle the layout rules. The -- way it works is that the Parser monad keeps track of a stack of -- LayoutContexts specifying the indentation of the layout blocks -- in scope. For instance, consider the following incomplete (Haskell) -- program: -- --
--   f x = x'
--     where
--       x' = case x of { True -> False; False -> ...
--   
-- -- At the ... the layout context would be -- --
--   [NoLayout, Layout 4, Layout 0]
--   
-- -- The closest layout block is the one containing the case -- branches. This block starts with an open brace ('{') and so -- doesn't use layout. The second closest block is the where -- clause. Here, there is no open brace so the block is started by the -- x' token which has indentation 4. Finally there is a -- top-level layout block with indentation 0. module Agda.Syntax.Parser.Layout -- | Executed upon lexing an open brace ('{'). Enters the -- NoLayout context. openBrace :: LexAction Token -- | Executed upon lexing a close brace ('}'). Exits the current -- layout context. This might look a bit funny--the lexer will happily -- use a close brace to close a context open by a virtual brace. This is -- not a problem since the parser will make sure the braces are -- appropriately matched. closeBrace :: LexAction Token -- | Executed for layout keywords. Enters the layout state and -- performs the given action. withLayout :: LexAction r -> LexAction r -- | Executed for the first token in each line (see bol). Checks the -- position of the token relative to the current layout context. If the -- token is -- -- -- -- If the current block doesn't use layout (i.e. it was started by -- openBrace) all positions are considered to be to the -- right. offsideRule :: LexAction Token -- | Start a new layout context. This is one of two ways to get out of the -- layout state (the other is openBrace). There are two -- possibilities: -- -- -- -- In the first case everything is fine and we enter a new layout context -- at the column of the current token. In the second case we have an -- empty layout block so we enter the empty_layout state. In both -- cases we return a virtual open brace without consuming any input. -- -- Entering a new state when we know we want to generate a virtual -- {} may seem a bit roundabout. The thing is that we can only -- generate one token at a time, so the way to generate two tokens is to -- generate the first one and then enter a state in which the only thing -- you can do is generate the second one. newLayoutContext :: LexAction Token -- | This action is only executed from the empty_layout state. It -- will exit this state, enter the bol state, and return a virtual -- close brace (closing the empty layout block started by -- newLayoutContext). emptyLayout :: LexAction Token -- | The parser is generated by Happy -- (http://www.haskell.org/happy). - - Ideally, ranges should be -- as precise as possible, to get messages that - emphasize precisely the -- faulting term(s) upon error. - - However, interactive highlighting is -- only applied at the end of each - mutual block, keywords are only -- highlighted once (see - Decl). So if the ranges of two -- declarations - interleave, one must ensure that keyword ranges are not -- included in - the intersection. (Otherwise they are uncolored by the -- interactive - highlighting.) - module Agda.Syntax.Parser.Parser -- | Parse a module. moduleParser :: Parser Module moduleNameParser :: Parser QName -- | Parse an expression. Could be used in interactions. exprParser :: Parser Expr -- | Parse the token stream. Used by the TeX compiler. tokensParser :: Parser [Token] -- | Test suite. tests :: IO Bool instance GHC.Show.Show Agda.Syntax.Parser.Parser.RHSOrTypeSigs module Agda.Syntax.Parser -- | Wrapped Parser type. data Parser a parse :: Parser a -> String -> IO a parseLiterate :: Parser a -> String -> IO a parsePosString :: Parser a -> Position -> String -> IO a parseFile' :: Parser a -> AbsolutePath -> IO a -- | Parses a module. moduleParser :: Parser Module -- | Parses a module name. moduleNameParser :: Parser QName -- | Parses an expression. exprParser :: Parser Expr -- | Gives the parsed token stream (including comments). tokensParser :: Parser [Token] -- | What you get if parsing fails. data ParseError ParseError :: Position -> String -> String -> String -> ParseError -- | where the error occured [errPos] :: ParseError -> Position -- | the remaining input [errInput] :: ParseError -> String -- | the previous token [errPrevToken] :: ParseError -> String -- | hopefully an explanation of what happened [errMsg] :: ParseError -> String -- | This module defines the exception handler. module Agda.Interaction.Exceptions handleParseException :: (ParseError -> IO a) -> ParseError -> IO a -- | Note that failOnException only catches ParseErrors. failOnException :: (Range -> Doc -> IO a) -> IO a -> IO a -- | Occurrences. module Agda.TypeChecking.Positivity.Occurrence -- | Subterm occurrences for positivity checking. The constructors are -- listed in increasing information they provide: Mixed <= JustPos -- <= StrictPos <= GuardPos <= Unused Mixed <= -- JustNeg <= Unused. data Occurrence -- | Arbitrary occurrence (positive and negative). Mixed :: Occurrence -- | Negative occurrence. JustNeg :: Occurrence -- | Positive occurrence, but not strictly positive. JustPos :: Occurrence -- | Strictly positive occurrence. StrictPos :: Occurrence -- | Guarded strictly positive occurrence (i.e., under ∞). For checking -- recursive records. GuardPos :: Occurrence Unused :: Occurrence -- | Occurrence is a complete lattice with least element -- Mixed and greatest element Unused. -- -- It forms a commutative semiring where oplus is meet (glb) and -- otimes is composition. Both operations are idempotent. -- -- For oplus, Unused is neutral (zero) and Mixed is -- dominant. For otimes, StrictPos is neutral (one) and -- Unused is dominant. prop_Occurrence_oplus_associative :: Occurrence -> Occurrence -> Occurrence -> Bool prop_Occurrence_oplus_ozero :: Occurrence -> Bool prop_Occurrence_oplus_commutative :: Occurrence -> Occurrence -> Bool prop_Occurrence_otimes_associative :: Occurrence -> Occurrence -> Occurrence -> Bool prop_Occurrence_otimes_oone :: Occurrence -> Bool prop_Occurrence_distributive :: Occurrence -> Occurrence -> Occurrence -> Bool prop_Occurrence_otimes_ozero :: Occurrence -> Bool prop_Occurrence_ostar :: Occurrence -> Bool -- | Tests. tests :: IO Bool instance GHC.Enum.Bounded Agda.TypeChecking.Positivity.Occurrence.Occurrence instance GHC.Enum.Enum Agda.TypeChecking.Positivity.Occurrence.Occurrence instance GHC.Classes.Ord Agda.TypeChecking.Positivity.Occurrence.Occurrence instance GHC.Classes.Eq Agda.TypeChecking.Positivity.Occurrence.Occurrence instance GHC.Show.Show Agda.TypeChecking.Positivity.Occurrence.Occurrence instance Control.DeepSeq.NFData Agda.TypeChecking.Positivity.Occurrence.Occurrence instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Positivity.Occurrence.Occurrence instance Test.QuickCheck.Arbitrary.Arbitrary Agda.TypeChecking.Positivity.Occurrence.Occurrence instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.TypeChecking.Positivity.Occurrence.Occurrence instance Agda.Utils.SemiRing.SemiRing Agda.TypeChecking.Positivity.Occurrence.Occurrence instance Agda.Utils.SemiRing.StarSemiRing Agda.TypeChecking.Positivity.Occurrence.Occurrence instance Agda.Utils.Null.Null Agda.TypeChecking.Positivity.Occurrence.Occurrence -- | Properties for graph library. module Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests -- | All tests as collected by quickCheckAll. -- -- Using quickCheckAll is convenient and superior to the manual -- enumeration of tests, since the name of the property is added -- automatically. tests :: IO Bool instance GHC.Show.Show Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.ExtendedNatural instance GHC.Classes.Ord Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.ExtendedNatural instance GHC.Classes.Eq Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.ExtendedNatural instance GHC.Show.Show Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.Connected instance GHC.Classes.Eq Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.Connected instance GHC.Classes.Ord Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.N instance GHC.Classes.Eq Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.N instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.N instance GHC.Show.Show Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.N instance Agda.Utils.SemiRing.SemiRing Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.Connected instance Agda.Utils.SemiRing.StarSemiRing Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.Connected instance Agda.Utils.SemiRing.SemiRing Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.ExtendedNatural instance Agda.Utils.SemiRing.StarSemiRing Agda.Utils.Graph.AdjacencyMap.Unidirectional.Tests.ExtendedNatural -- | The abstract syntax. This is what you get after desugaring and scope -- analysis of the concrete syntax. The type checker works on abstract -- syntax, producing internal syntax (Agda.Syntax.Internal). module Agda.Syntax.Abstract type Color = Expr type Arg a = Arg Color a type Dom a = Dom Color a type NamedArg a = NamedArg Color a type ArgInfo = ArgInfo Color type Args = [NamedArg Expr] -- | Expressions after scope checking (operators parsed, names resolved). data Expr -- | Bound variable. Var :: Name -> Expr -- | Constant: axiom, function, data or record type. Def :: QName -> Expr -- | Projection. Proj :: QName -> Expr -- | Constructor. Con :: AmbiguousQName -> Expr -- | Pattern synonym. PatternSyn :: QName -> Expr -- | Literal. Lit :: Literal -> Expr -- | Meta variable for interaction. The InteractionId is usually -- identical with the metaNumber of MetaInfo. However, if -- you want to print an interaction meta as just ? instead of -- ?n, you should set the metaNumber to Nothing -- while keeping the InteractionId. QuestionMark :: MetaInfo -> InteractionId -> Expr -- | Meta variable for hidden argument (must be inferred locally). Underscore :: MetaInfo -> Expr -- | Ordinary (binary) application. App :: ExprInfo -> Expr -> (NamedArg Expr) -> Expr -- | With application. WithApp :: ExprInfo -> Expr -> [Expr] -> Expr -- | λ bs → e. Lam :: ExprInfo -> LamBinding -> Expr -> Expr -- | λ() or λ{}. AbsurdLam :: ExprInfo -> Hiding -> Expr ExtendedLam :: ExprInfo -> DefInfo -> QName -> [Clause] -> Expr -- | Dependent function space Γ → A. Pi :: ExprInfo -> Telescope -> Expr -> Expr -- | Non-dependent function space. Fun :: ExprInfo -> (Arg Expr) -> Expr -> Expr -- | Set, Set1, Set2, ... Set :: ExprInfo -> Integer -> Expr -- | Prop (no longer supported, used as dummy type). Prop :: ExprInfo -> Expr -- | let bs in e. Let :: ExprInfo -> [LetBinding] -> Expr -> Expr -- | Only used when printing telescopes. ETel :: Telescope -> Expr -- | Record construction. Rec :: ExprInfo -> Assigns -> Expr -- | Record update. RecUpdate :: ExprInfo -> Expr -> Assigns -> Expr -- | Scope annotation. ScopedExpr :: ScopeInfo -> Expr -> Expr -- | Binds Name to current type in Expr. QuoteGoal :: ExprInfo -> Name -> Expr -> Expr -- | Binds Name to current context in Expr. QuoteContext :: ExprInfo -> Name -> Expr -> Expr -- | Quote an identifier QName. Quote :: ExprInfo -> Expr -- | Quote a term. QuoteTerm :: ExprInfo -> Expr -- | The splicing construct: unquote ... Unquote :: ExprInfo -> Expr -- | For printing DontCare from Syntax.Internal. DontCare :: Expr -> Expr -- | Record field assignment f = e. type Assign = (Name, Expr) type Assigns = [Assign] -- | Is a type signature a postulate or a function signature? data Axiom -- | A function signature. FunSig :: Axiom -- | Not a function signature, i.e., a postulate (in user input) or another -- (e.g. data/record) type signature (internally). NoFunSig :: Axiom -- | Renaming (generic). type Ren a = [(a, a)] data Declaration -- | type signature (can be irrelevant and colored, but not hidden) Axiom :: Axiom -> DefInfo -> ArgInfo -> QName -> Expr -> Declaration -- | record field Field :: DefInfo -> QName -> (Arg Expr) -> Declaration -- | primitive function Primitive :: DefInfo -> QName -> Expr -> Declaration -- | a bunch of mutually recursive definitions Mutual :: MutualInfo -> [Declaration] -> Declaration Section :: ModuleInfo -> ModuleName -> [TypedBindings] -> [Declaration] -> Declaration Apply :: ModuleInfo -> ModuleName -> ModuleApplication -> (Ren QName) -> (Ren ModuleName) -> Declaration Import :: ModuleInfo -> ModuleName -> Declaration Pragma :: Range -> Pragma -> Declaration -- | only retained for highlighting purposes Open :: ModuleInfo -> ModuleName -> Declaration -- | sequence of function clauses FunDef :: DefInfo -> QName -> Delayed -> [Clause] -> Declaration -- | lone data signature ^ the LamBindings are DomainFree and -- binds the parameters of the datatype. DataSig :: DefInfo -> QName -> Telescope -> Expr -> Declaration -- | the LamBindings are DomainFree and binds the parameters -- of the datatype. DataDef :: DefInfo -> QName -> [LamBinding] -> [Constructor] -> Declaration -- | lone record signature RecSig :: DefInfo -> QName -> Telescope -> Expr -> Declaration -- | The Expr gives the constructor type telescope, (x1 : -- A1)..(xn : An) -> Prop, and the optional name is the -- constructor's name. RecDef :: DefInfo -> QName -> (Maybe (Ranged Induction)) -> (Maybe QName) -> [LamBinding] -> Expr -> [Declaration] -> Declaration -- | Only for highlighting purposes PatternSynDef :: QName -> [Arg Name] -> Pattern -> Declaration UnquoteDecl :: MutualInfo -> DefInfo -> QName -> Expr -> Declaration -- | scope annotation ScopedDecl :: ScopeInfo -> [Declaration] -> Declaration class GetDefInfo a getDefInfo :: GetDefInfo a => a -> Maybe DefInfo data ModuleApplication -- | tel. M args: applies M to args and -- abstracts tel. SectionApp :: Telescope -> ModuleName -> [NamedArg Expr] -> ModuleApplication -- |
--   M {{...}}
--   
RecordModuleIFS :: ModuleName -> ModuleApplication data Pragma OptionsPragma :: [String] -> Pragma BuiltinPragma :: String -> Expr -> Pragma -- | Builtins that do not come with a definition, but declare a name for an -- Agda concept. BuiltinNoDefPragma :: String -> QName -> Pragma RewritePragma :: QName -> Pragma CompiledPragma :: QName -> String -> Pragma CompiledExportPragma :: QName -> String -> Pragma CompiledTypePragma :: QName -> String -> Pragma CompiledDataPragma :: QName -> String -> [String] -> Pragma CompiledEpicPragma :: QName -> String -> Pragma CompiledJSPragma :: QName -> String -> Pragma StaticPragma :: QName -> Pragma EtaPragma :: QName -> Pragma -- | Bindings that are valid in a let. data LetBinding -- |
--   LetBind info rel name type defn
--   
LetBind :: LetInfo -> ArgInfo -> Name -> Expr -> Expr -> LetBinding -- | Irrefutable pattern binding. LetPatBind :: LetInfo -> Pattern -> Expr -> LetBinding -- | LetApply mi newM (oldM args) renaming moduleRenaming. LetApply :: ModuleInfo -> ModuleName -> ModuleApplication -> (Ren QName) -> (Ren ModuleName) -> LetBinding -- | only for highlighting and abstractToConcrete LetOpen :: ModuleInfo -> ModuleName -> LetBinding -- | Only Axioms. type TypeSignature = Declaration type Constructor = TypeSignature type Field = TypeSignature -- | A lambda binding is either domain free or typed. data LamBinding -- | . x or {x} or .x or .{x} DomainFree :: ArgInfo -> Name -> LamBinding -- | . (xs:e) or {xs:e} or (let Ds) DomainFull :: TypedBindings -> LamBinding -- | Typed bindings with hiding information. data TypedBindings -- | . (xs : e) or {xs : e} TypedBindings :: Range -> (Arg TypedBinding) -> TypedBindings -- | A typed binding. Appears in dependent function spaces, typed lambdas, -- and telescopes. It might be tempting to simplify this to only bind a -- single name at a time, and translate, say, (x y : A) to -- (x : A)(y : A) before type-checking. However, this would be -- slightly problematic: -- --
    --
  1. We would have to typecheck the type A several times.
  2. --
  3. If A contains a meta variable or hole, it would be -- duplicated by such a translation.
  4. --
-- -- While 1. is only slightly inefficient, 2. would be an outright bug. -- Duplicating A could not be done naively, we would have to -- make sure that the metas of the copy are aliases of the metas of the -- original. data TypedBinding -- | As in telescope (x y z : A) or type (x y z : A) -> -- B. TBind :: Range -> [WithHiding Name] -> Expr -> TypedBinding -- | E.g. (let x = e) or (let open M). TLet :: Range -> [LetBinding] -> TypedBinding type Telescope = [TypedBindings] -- | We could throw away where clauses at this point and translate -- them to let. It's not obvious how to remember that the -- let was really a where clause though, so for the -- time being we keep it here. data Clause' lhs Clause :: lhs -> RHS -> [Declaration] -> Clause' lhs [clauseLHS] :: Clause' lhs -> lhs [clauseRHS] :: Clause' lhs -> RHS [clauseWhereDecls] :: Clause' lhs -> [Declaration] type Clause = Clause' LHS type SpineClause = Clause' SpineLHS data RHS RHS :: Expr -> RHS AbsurdRHS :: RHS -- | The QName is the name of the with function. WithRHS :: QName -> [Expr] -> [Clause] -> RHS -- | The QNames are the names of the generated with functions. One -- for each Expr. The RHS shouldn't be another -- RewriteRHS. RewriteRHS :: [(QName, Expr)] -> RHS -> [Declaration] -> RHS -- | The lhs of a clause in spine view (inside-out). Projection patterns -- are contained in spLhsPats, represented as DefP d -- []. data SpineLHS SpineLHS :: LHSInfo -> QName -> [NamedArg Pattern] -> [Pattern] -> SpineLHS -- | Range. [spLhsInfo] :: SpineLHS -> LHSInfo -- | Name of function we are defining. [spLhsDefName] :: SpineLHS -> QName -- | Function parameters (patterns). [spLhsPats] :: SpineLHS -> [NamedArg Pattern] -- | with patterns (after |). [spLhsWithPats] :: SpineLHS -> [Pattern] -- | The lhs of a clause in focused (projection-application) view -- (outside-in). Projection patters are represented as LHSProjs. data LHS LHS :: LHSInfo -> LHSCore -> [Pattern] -> LHS -- | Range. [lhsInfo] :: LHS -> LHSInfo -- | Copatterns. [lhsCore] :: LHS -> LHSCore -- | with patterns (after |). [lhsWithPats] :: LHS -> [Pattern] -- | The lhs minus with-patterns in projection-application view. -- Parameterised over the type e of dot patterns. data LHSCore' e -- | The head applied to ordinary patterns. LHSHead :: QName -> [NamedArg (Pattern' e)] -> LHSCore' e -- | Head f. [lhsDefName] :: LHSCore' e -> QName -- | Applied to patterns ps. [lhsPats] :: LHSCore' e -> [NamedArg (Pattern' e)] -- | Projection LHSProj :: QName -> [NamedArg (Pattern' e)] -> NamedArg (LHSCore' e) -> [NamedArg (Pattern' e)] -> LHSCore' e -- | Record projection identifier. [lhsDestructor] :: LHSCore' e -> QName -- | Indices of the projection. Currently none [], since we do not -- have indexed records. [lhsPatsLeft] :: LHSCore' e -> [NamedArg (Pattern' e)] -- | Main branch. [lhsFocus] :: LHSCore' e -> NamedArg (LHSCore' e) -- | Further applied to patterns. [lhsPatsRight] :: LHSCore' e -> [NamedArg (Pattern' e)] type LHSCore = LHSCore' Expr -- | Convert a focused lhs to spine view and back. class LHSToSpine a b lhsToSpine :: LHSToSpine a b => a -> b spineToLhs :: LHSToSpine a b => b -> a -- | Clause instance. -- | List instance (for clauses). -- | LHS instance. lhsCoreToSpine :: LHSCore' e -> QNamed [NamedArg (Pattern' e)] spineToLhsCore :: QNamed [NamedArg (Pattern' e)] -> LHSCore' e -- | Add applicative patterns (non-projection patterns) to the right. lhsCoreApp :: LHSCore' e -> [NamedArg (Pattern' e)] -> LHSCore' e -- | Add projection and applicative patterns to the right. lhsCoreAddSpine :: LHSCore' e -> [NamedArg (Pattern' e)] -> LHSCore' e -- | Used for checking pattern linearity. lhsCoreAllPatterns :: LHSCore' e -> [Pattern' e] -- | Used in AbstractToConcrete. lhsCoreToPattern :: LHSCore -> Pattern mapLHSHead :: (QName -> [NamedArg Pattern] -> LHSCore) -> LHSCore -> LHSCore -- | Parameterised over the type of dot patterns. data Pattern' e VarP :: Name -> Pattern' e ConP :: ConPatInfo -> AmbiguousQName -> [NamedArg (Pattern' e)] -> Pattern' e -- | Defined pattern: function definition f ps or destructor -- pattern d p ps. DefP :: PatInfo -> QName -> [NamedArg (Pattern' e)] -> Pattern' e -- | Underscore pattern entered by user. Or generated at type checking for -- implicit arguments. WildP :: PatInfo -> Pattern' e AsP :: PatInfo -> Name -> (Pattern' e) -> Pattern' e DotP :: PatInfo -> e -> Pattern' e AbsurdP :: PatInfo -> Pattern' e LitP :: Literal -> Pattern' e PatternSynP :: PatInfo -> QName -> [NamedArg (Pattern' e)] -> Pattern' e type Pattern = Pattern' Expr type Patterns = [NamedArg Pattern] -- | Check whether we are a projection pattern. class IsProjP a isProjP :: IsProjP a => a -> Maybe QName -- | Literal equality of patterns, ignoring dot patterns -- | Extracts all the names which are declared in a Declaration. -- This does not include open public or let expressions, but it does -- include local modules, where clauses and the names of extended -- lambdas. class AllNames a allNames :: AllNames a => a -> Seq QName -- | The name defined by the given axiom. -- -- Precondition: The declaration has to be a (scoped) Axiom. axiomName :: Declaration -> QName -- | Are we in an abstract block? -- -- In that case some definition is abstract. class AnyAbstract a anyAbstract :: AnyAbstract a => a -> Bool app :: Expr -> [NamedArg Expr] -> Expr patternToExpr :: Pattern -> Expr type PatternSynDefn = ([Arg Name], Pattern) type PatternSynDefns = Map QName PatternSynDefn lambdaLiftExpr :: [Name] -> Expr -> Expr substPattern :: [(Name, Pattern)] -> Pattern -> Pattern class SubstExpr a substExpr :: SubstExpr a => [(Name, Expr)] -> a -> a insertImplicitPatSynArgs :: HasRange a => (Range -> a) -> Range -> [Arg Name] -> [NamedArg a] -> Maybe ([(Name, a)], [Arg Name]) instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Abstract.Declaration Agda.Syntax.Common.RString instance Agda.Syntax.Abstract.AllNames a => Agda.Syntax.Abstract.AllNames [a] instance Agda.Syntax.Abstract.AllNames a => Agda.Syntax.Abstract.AllNames (GHC.Base.Maybe a) instance Agda.Syntax.Abstract.AllNames a => Agda.Syntax.Abstract.AllNames (Agda.Syntax.Abstract.Arg a) instance Agda.Syntax.Abstract.AllNames a => Agda.Syntax.Abstract.AllNames (Agda.Syntax.Common.Named name a) instance (Agda.Syntax.Abstract.AllNames a, Agda.Syntax.Abstract.AllNames b) => Agda.Syntax.Abstract.AllNames (a, b) instance Agda.Syntax.Abstract.AllNames Agda.Syntax.Abstract.Name.QName instance Agda.Syntax.Abstract.AllNames Agda.Syntax.Abstract.Declaration instance Agda.Syntax.Abstract.AllNames Agda.Syntax.Abstract.Clause instance Agda.Syntax.Abstract.AllNames Agda.Syntax.Abstract.RHS instance Agda.Syntax.Abstract.AllNames Agda.Syntax.Abstract.Expr instance Agda.Syntax.Abstract.AllNames Agda.Syntax.Abstract.LamBinding instance Agda.Syntax.Abstract.AllNames Agda.Syntax.Abstract.TypedBindings instance Agda.Syntax.Abstract.AllNames Agda.Syntax.Abstract.TypedBinding instance Agda.Syntax.Abstract.AllNames Agda.Syntax.Abstract.LetBinding instance Agda.Syntax.Abstract.AllNames Agda.Syntax.Abstract.ModuleApplication instance Agda.Syntax.Abstract.AnyAbstract a => Agda.Syntax.Abstract.AnyAbstract [a] instance Agda.Syntax.Abstract.AnyAbstract Agda.Syntax.Abstract.Declaration instance Agda.Syntax.Abstract.SubstExpr a => Agda.Syntax.Abstract.SubstExpr [a] instance Agda.Syntax.Abstract.SubstExpr a => Agda.Syntax.Abstract.SubstExpr (Agda.Syntax.Abstract.Arg a) instance Agda.Syntax.Abstract.SubstExpr a => Agda.Syntax.Abstract.SubstExpr (Agda.Syntax.Common.Named name a) instance (Agda.Syntax.Abstract.SubstExpr a, Agda.Syntax.Abstract.SubstExpr b) => Agda.Syntax.Abstract.SubstExpr (a, b) instance Agda.Syntax.Abstract.SubstExpr Agda.Syntax.Concrete.Name.Name instance Agda.Syntax.Abstract.SubstExpr Agda.Syntax.Abstract.Expr instance Agda.Syntax.Abstract.SubstExpr Agda.Syntax.Abstract.LetBinding instance Agda.Syntax.Abstract.SubstExpr Agda.Syntax.Abstract.TypedBindings instance Agda.Syntax.Abstract.SubstExpr Agda.Syntax.Abstract.TypedBinding instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Abstract.Declaration Agda.Syntax.Info.ModuleInfo instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Abstract.Declaration Agda.Syntax.Abstract.Name.ModuleName instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Abstract.Declaration Agda.Syntax.Abstract.Declaration instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Abstract.Declaration Agda.Syntax.Abstract.Pattern instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Abstract.Declaration Agda.Syntax.Abstract.TypedBinding instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Abstract.Declaration Agda.Syntax.Abstract.LamBinding instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Abstract.Declaration Agda.Syntax.Abstract.LetBinding instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Abstract.Declaration Agda.Syntax.Abstract.Expr instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Abstract.Declaration Agda.Syntax.Abstract.Name.AmbiguousQName instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Abstract.Declaration Agda.Syntax.Abstract.Name.QName instance GHC.Show.Show Agda.Syntax.Abstract.SpineLHS instance GHC.Show.Show Agda.Syntax.Abstract.Pragma instance GHC.Show.Show Agda.Syntax.Abstract.LamBinding instance GHC.Show.Show Agda.Syntax.Abstract.ModuleApplication instance GHC.Show.Show Agda.Syntax.Abstract.LetBinding instance GHC.Show.Show Agda.Syntax.Abstract.TypedBinding instance GHC.Show.Show Agda.Syntax.Abstract.TypedBindings instance GHC.Show.Show Agda.Syntax.Abstract.Declaration instance GHC.Show.Show Agda.Syntax.Abstract.RHS instance Data.Traversable.Traversable Agda.Syntax.Abstract.Clause' instance Data.Foldable.Foldable Agda.Syntax.Abstract.Clause' instance GHC.Base.Functor Agda.Syntax.Abstract.Clause' instance GHC.Show.Show lhs => GHC.Show.Show (Agda.Syntax.Abstract.Clause' lhs) instance Data.Traversable.Traversable Agda.Syntax.Abstract.LHSCore' instance Data.Foldable.Foldable Agda.Syntax.Abstract.LHSCore' instance GHC.Base.Functor Agda.Syntax.Abstract.LHSCore' instance GHC.Show.Show e => GHC.Show.Show (Agda.Syntax.Abstract.LHSCore' e) instance GHC.Classes.Eq (Agda.Syntax.Abstract.LHSCore' e) instance GHC.Show.Show Agda.Syntax.Abstract.LHS instance GHC.Show.Show Agda.Syntax.Abstract.Expr instance Data.Traversable.Traversable Agda.Syntax.Abstract.Pattern' instance Data.Foldable.Foldable Agda.Syntax.Abstract.Pattern' instance GHC.Base.Functor Agda.Syntax.Abstract.Pattern' instance GHC.Show.Show e => GHC.Show.Show (Agda.Syntax.Abstract.Pattern' e) instance GHC.Show.Show Agda.Syntax.Abstract.Axiom instance GHC.Classes.Ord Agda.Syntax.Abstract.Axiom instance GHC.Classes.Eq Agda.Syntax.Abstract.Axiom instance GHC.Classes.Eq Agda.Syntax.Abstract.Color instance GHC.Classes.Ord Agda.Syntax.Abstract.Color instance Agda.Syntax.Abstract.GetDefInfo Agda.Syntax.Abstract.Declaration instance Agda.Syntax.Abstract.LHSToSpine Agda.Syntax.Abstract.Clause Agda.Syntax.Abstract.SpineClause instance Agda.Syntax.Abstract.LHSToSpine a b => Agda.Syntax.Abstract.LHSToSpine [a] [b] instance Agda.Syntax.Abstract.LHSToSpine Agda.Syntax.Abstract.LHS Agda.Syntax.Abstract.SpineLHS instance Agda.Syntax.Abstract.IsProjP (Agda.Syntax.Abstract.Pattern' e) instance Agda.Syntax.Abstract.IsProjP a => Agda.Syntax.Abstract.IsProjP (Agda.Syntax.Common.Arg c a) instance Agda.Syntax.Abstract.IsProjP a => Agda.Syntax.Abstract.IsProjP (Agda.Syntax.Common.Named n a) instance GHC.Classes.Eq (Agda.Syntax.Abstract.Pattern' e) instance GHC.Classes.Eq Agda.Syntax.Abstract.LHS instance Agda.Syntax.Common.Underscore Agda.Syntax.Abstract.Expr instance Agda.Syntax.Common.LensHiding Agda.Syntax.Abstract.TypedBindings instance Agda.Syntax.Common.LensHiding Agda.Syntax.Abstract.LamBinding instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.LamBinding instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.TypedBindings instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.TypedBinding instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.Expr instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.Declaration instance Agda.Syntax.Position.HasRange (Agda.Syntax.Abstract.Pattern' e) instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.SpineLHS instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.LHS instance Agda.Syntax.Position.HasRange (Agda.Syntax.Abstract.LHSCore' e) instance Agda.Syntax.Position.HasRange a => Agda.Syntax.Position.HasRange (Agda.Syntax.Abstract.Clause' a) instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.RHS instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.LetBinding instance Agda.Syntax.Position.SetRange (Agda.Syntax.Abstract.Pattern' a) instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.LamBinding instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.TypedBindings instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.TypedBinding instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.Expr instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.Declaration instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.ModuleApplication instance Agda.Syntax.Position.KillRange e => Agda.Syntax.Position.KillRange (Agda.Syntax.Abstract.Pattern' e) instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.SpineLHS instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.LHS instance Agda.Syntax.Position.KillRange e => Agda.Syntax.Position.KillRange (Agda.Syntax.Abstract.LHSCore' e) instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Agda.Syntax.Abstract.Clause' a) instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.RHS instance Agda.Syntax.Position.KillRange Agda.Syntax.Abstract.LetBinding module Agda.Syntax.Abstract.Views data AppView Application :: Expr -> [NamedArg Expr] -> AppView -- | Gather applications to expose head and spine. -- -- Note: everything is an application, possibly of itself to 0 arguments appView :: Expr -> AppView unAppView :: AppView -> Expr -- | Gather top-level AsPatterns to expose underlying pattern. asView :: Pattern -> ([Name], Pattern) -- | Check whether we are dealing with a universe. isSet :: Expr -> Bool -- | Remove top ScopedExpr wrappers. unScope :: Expr -> Expr -- | Remove ScopedExpr wrappers everywhere. deepUnScope :: Expr -> Expr -- | Apply an expression rewriting to every subexpression, inside-out. See -- Agda.Syntax.Internal.Generic. class ExprLike a where recurseExpr = traverse . recurseExpr foldExpr f = getConst . recurseExpr (\ pre post -> Const $ f pre) traverseExpr f = recurseExpr (\ pre post -> f =<< post) mapExpr f e = runIdentity $ traverseExpr (Identity . f) e -- | The first expression is pre-traversal, the second one post-traversal. recurseExpr :: (ExprLike a, Applicative m) => (Expr -> m Expr -> m Expr) -> a -> m a foldExpr :: (ExprLike a, Monoid m) => (Expr -> m) -> a -> m traverseExpr :: (ExprLike a, Monad m, Applicative m) => (Expr -> m Expr) -> a -> m a mapExpr :: ExprLike a => (Expr -> Expr) -> (a -> a) -- | TODO: currently does not go into colors. -- | TODO: currently does not go into clauses. instance Agda.Syntax.Abstract.Views.ExprLike Agda.Syntax.Abstract.Expr instance Agda.Syntax.Abstract.Views.ExprLike a => Agda.Syntax.Abstract.Views.ExprLike (Agda.Syntax.Common.Arg c a) instance Agda.Syntax.Abstract.Views.ExprLike a => Agda.Syntax.Abstract.Views.ExprLike (Agda.Syntax.Common.Named x a) instance Agda.Syntax.Abstract.Views.ExprLike a => Agda.Syntax.Abstract.Views.ExprLike [a] instance Agda.Syntax.Abstract.Views.ExprLike a => Agda.Syntax.Abstract.Views.ExprLike (x, a) instance Agda.Syntax.Abstract.Views.ExprLike Agda.Syntax.Abstract.LamBinding instance Agda.Syntax.Abstract.Views.ExprLike Agda.Syntax.Abstract.TypedBindings instance Agda.Syntax.Abstract.Views.ExprLike Agda.Syntax.Abstract.TypedBinding instance Agda.Syntax.Abstract.Views.ExprLike Agda.Syntax.Abstract.LetBinding instance Agda.Syntax.Abstract.Views.ExprLike a => Agda.Syntax.Abstract.Views.ExprLike (Agda.Syntax.Abstract.Pattern' a) instance Agda.Syntax.Abstract.Views.ExprLike (Agda.Syntax.Abstract.Clause' a) module Agda.Utils.Permutation -- | Partial permutations. Examples: -- -- permute [1,2,0] [x0,x1,x2] = [x1,x2,x0] (proper permutation). -- -- permute [1,0] [x0,x1,x2] = [x1,x0] (partial permuation). -- -- permute [1,0,1,2] [x0,x1,x2] = [x1,x0,x1,x2] (not a -- permutation because not invertible). -- -- Agda typing would be: Perm : {m : Nat}(n : Nat) -> Vec (Fin n) -- m -> Permutation m is the size of the -- permutation. data Permutation Perm :: Int -> [Int] -> Permutation [permRange] :: Permutation -> Int [permPicks] :: Permutation -> [Int] -- | permute [1,2,0] [x0,x1,x2] = [x1,x2,x0] More precisely, -- permute indices list = sublist, generates sublist -- from list by picking the elements of list as indicated by -- indices. permute [1,3,0] [x0,x1,x2,x3] = [x1,x3,x0] -- -- Agda typing: permute (Perm {m} n is) : Vec A m -> Vec A n permute :: Permutation -> [a] -> [a] safePermute :: Permutation -> [a] -> [Maybe a] -- | Invert a Permutation on a partial finite int map. inversePermute -- perm f = f' such that permute perm f' = f -- -- Example, with map represented as [Maybe a]: f = -- [Nothing, Just a, Just b ] perm = Perm 4 [3,0,2] f' = [ Just a , -- Nothing , Just b , Nothing ] Zipping perm with -- f gives [(0,a),(2,b)], after compression with -- catMaybes. This is an IntMap which can easily -- written out into a substitution again. class InversePermute a b inversePermute :: InversePermute a b => Permutation -> a -> b -- | Identity permutation. idP :: Int -> Permutation -- | Restrict a permutation to work on n elements, discarding -- picks >=n. takeP :: Int -> Permutation -> Permutation -- | Pick the elements that are not picked by the permutation. droppedP :: Permutation -> Permutation -- | liftP k takes a Perm {m} n to a Perm {m+k} -- (n+k). Analogous to liftS, but Permutations operate on de -- Bruijn LEVELS, not indices. liftP :: Int -> Permutation -> Permutation -- |
--   permute (compose p1 p2) == permute p1 . permute p2
--   
composeP :: Permutation -> Permutation -> Permutation -- | invertP err p is the inverse of p where defined, -- otherwise defaults to err. composeP p (invertP err p) == -- p invertP :: Int -> Permutation -> Permutation -- | Turn a possible non-surjective permutation into a surjective -- permutation. compactP :: Permutation -> Permutation -- |
--   permute (reverseP p) xs ==
--       reverse $ permute p $ reverse xs
--   
-- -- Example: permute (reverseP (Perm 4 [1,3,0])) [x0,x1,x2,x3] == -- permute (Perm 4 $ map (3-) [0,3,1]) [x0,x1,x2,x3] == permute (Perm 4 -- [3,0,2]) [x0,x1,x2,x3] == [x3,x0,x2] == reverse [x2,x0,x3] == reverse -- $ permute (Perm 4 [1,3,0]) [x3,x2,x1,x0] == reverse $ permute (Perm 4 -- [1,3,0]) $ reverse [x0,x1,x2,x3] -- -- With reverseP, you can convert a permutation on de Bruijn -- indices to one on de Bruijn levels, and vice versa. reverseP :: Permutation -> Permutation -- | permPicks (flipP p) = permute p (downFrom (permRange p)) or -- permute (flipP (Perm n xs)) [0..n-1] = permute (Perm n xs) -- (downFrom n) -- -- Can be use to turn a permutation from (de Bruijn) levels to levels to -- one from levels to indices. -- -- See numberPatVars. flipP :: Permutation -> Permutation -- | expandP i n π in the domain of π replace the -- ith element by n elements. expandP :: Int -> Int -> Permutation -> Permutation -- | Stable topologic sort. The first argument decides whether its first -- argument is an immediate parent to its second argument. topoSort :: (a -> a -> Bool) -> [a] -> Maybe Permutation -- | Delayed dropping which allows undropping. data Drop a Drop :: Int -> a -> Drop a -- | Non-negative number of things to drop. [dropN] :: Drop a -> Int -- | Where to drop from. [dropFrom] :: Drop a -> a -- | Things that support delayed dropping. class DoDrop a where dropMore n (Drop m xs) = Drop (m + n) xs unDrop n (Drop m xs) | n <= m = Drop (m - n) xs | otherwise = (throwImpossible (Impossible "src/full/Agda/Utils/Permutation.hs" 249)) doDrop :: DoDrop a => Drop a -> a dropMore :: DoDrop a => Int -> Drop a -> Drop a unDrop :: DoDrop a => Int -> Drop a -> Drop a instance Data.Traversable.Traversable Agda.Utils.Permutation.Drop instance Data.Foldable.Foldable Agda.Utils.Permutation.Drop instance GHC.Base.Functor Agda.Utils.Permutation.Drop instance GHC.Show.Show a => GHC.Show.Show (Agda.Utils.Permutation.Drop a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Utils.Permutation.Drop a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Utils.Permutation.Drop a) instance GHC.Classes.Eq Agda.Utils.Permutation.Permutation instance GHC.Show.Show Agda.Utils.Permutation.Permutation instance Agda.Utils.Size.Sized Agda.Utils.Permutation.Permutation instance Agda.Utils.Null.Null Agda.Utils.Permutation.Permutation instance Agda.Syntax.Position.KillRange Agda.Utils.Permutation.Permutation instance Agda.Utils.Permutation.InversePermute [GHC.Base.Maybe a] [(GHC.Types.Int, a)] instance Agda.Utils.Permutation.InversePermute [GHC.Base.Maybe a] (Data.IntMap.Base.IntMap a) instance Agda.Utils.Permutation.InversePermute [GHC.Base.Maybe a] [GHC.Base.Maybe a] instance Agda.Utils.Permutation.InversePermute (GHC.Types.Int -> a) [GHC.Base.Maybe a] instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Agda.Utils.Permutation.Drop a) instance Agda.Utils.Permutation.DoDrop [a] instance Agda.Utils.Permutation.DoDrop Agda.Utils.Permutation.Permutation instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Utils.Permutation.Permutation module Agda.Syntax.Internal type Color = Term type ArgInfo = ArgInfo Color type Arg a = Arg Color a type Dom a = Dom Color a type NamedArg a = NamedArg Color a -- | Type of argument lists. type Args = [Arg Term] type NamedArgs = [NamedArg Term] -- | Store the names of the record fields in the constructor. This allows -- reduction of projection redexes outside of TCM. For instance, during -- substitution and application. data ConHead ConHead :: QName -> Induction -> [QName] -> ConHead -- | The name of the constructor. [conName] :: ConHead -> QName -- | Record constructors can be coinductive. [conInductive] :: ConHead -> Induction -- | The name of the record fields. Empty list for data constructors. -- Arg is not needed here since it is stored in the constructor -- args. [conFields] :: ConHead -> [QName] class LensConName a where setConName = mapConName . const mapConName f a = setConName (f (getConName a)) a getConName :: LensConName a => a -> QName setConName :: LensConName a => QName -> a -> a mapConName :: LensConName a => (QName -> QName) -> a -> a -- | Raw values. -- -- Def is used for both defined and undefined constants. Assume -- there is a type declaration and a definition for every constant, even -- if the definition is an empty list of clauses. data Term -- | x es neutral Var :: {-# UNPACK #-} !Int -> Elims -> Term -- | Terms are beta normal. Relevance is ignored Lam :: ArgInfo -> (Abs Term) -> Term -- | Only used by unquote --> reify. Should never appear elsewhere. ExtLam :: [Clause] -> Args -> Term Lit :: Literal -> Term -- | f es, possibly a delta/iota-redex Def :: QName -> Elims -> Term -- |
--   c vs
--   
Con :: ConHead -> Args -> Term -- | dependent or non-dependent function space Pi :: (Dom Type) -> (Abs Type) -> Term Sort :: Sort -> Term Level :: Level -> Term MetaV :: {-# UNPACK #-} !MetaId -> Elims -> Term -- | Irrelevant stuff in relevant position, but created in an irrelevant -- context. Basically, an internal version of the irrelevance axiom -- .irrAx : .A -> A. DontCare :: Term -> Term -- | Explicit sharing Shared :: !(Ptr Term) -> Term -- | Eliminations, subsuming applications and projections. data Elim' a Apply :: (Arg a) -> Elim' a -- | name of a record projection Proj :: QName -> Elim' a type Elim = Elim' Term type Elims = [Elim] eliminations ordered left-to-right. -- | Names in binders and arguments. type ArgName = String argNameToString :: ArgName -> String stringToArgName :: String -> ArgName appendArgNames :: ArgName -> ArgName -> ArgName nameToArgName :: Name -> ArgName -- | Binder. Abs: The bound variable might appear in the body. -- NoAbs is pseudo-binder, it does not introduce a fresh variable, -- similar to the const of Haskell. data Abs a -- | The body has (at least) one free variable. Danger: unAbs -- doesn't shift variables properly Abs :: ArgName -> a -> Abs a [absName] :: Abs a -> ArgName [unAbs] :: Abs a -> a NoAbs :: ArgName -> a -> Abs a [absName] :: Abs a -> ArgName [unAbs] :: Abs a -> a -- | Types are terms with a sort annotation. data Type' a El :: Sort -> a -> Type' a [_getSort] :: Type' a -> Sort [unEl] :: Type' a -> a type Type = Type' Term class LensSort a where getSort a = a ^. lensSort lensSort :: LensSort a => Lens' Sort a getSort :: LensSort a => a -> Sort -- | Sequence of types. An argument of the first type is bound in later -- types and so on. data Tele a EmptyTel :: Tele a -- | Abs is never NoAbs. ExtendTel :: a -> (Abs (Tele a)) -> Tele a type Telescope = Tele (Dom Type) -- | A traversal for the names in a telescope. mapAbsNamesM :: Applicative m => (ArgName -> m ArgName) -> Tele a -> m (Tele a) mapAbsNames :: (ArgName -> ArgName) -> Tele a -> Tele a replaceEmptyName :: ArgName -> Tele a -> Tele a -- | Sorts. data Sort -- | Set ℓ. Type :: Level -> Sort -- | Dummy sort. Prop :: Sort -- | Setω. Inf :: Sort -- | SizeUniv, a sort inhabited by type Size. SizeUniv :: Sort -- | Dependent least upper bound. If the free variable occurs in the second -- sort, the whole thing should reduce to Inf, otherwise it's the normal -- lub. DLub :: Sort -> (Abs Sort) -> Sort -- | A level is a maximum expression of 0..n PlusLevel expressions -- each of which is a number or an atom plus a number. -- -- The empty maximum is the canonical representation for level 0. newtype Level Max :: [PlusLevel] -> Level data PlusLevel -- | n, to represent Setₙ. ClosedLevel :: Integer -> PlusLevel -- | n + ℓ. Plus :: Integer -> LevelAtom -> PlusLevel -- | An atomic term of type Level. data LevelAtom -- | A meta variable targeting Level under some eliminations. MetaLevel :: MetaId -> Elims -> LevelAtom -- | A term of type Level whose reduction is blocked by a meta. BlockedLevel :: MetaId -> Term -> LevelAtom -- | A neutral term of type Level. NeutralLevel :: NotBlocked -> Term -> LevelAtom -- | Introduced by instantiate, removed by reduce. UnreducedLevel :: Term -> LevelAtom -- | Even if we are not stuck on a meta during reduction we can fail to -- reduce a definition by pattern matching for another reason. data NotBlocked -- | The Elim is neutral and blocks a pattern match. StuckOn :: Elim -> NotBlocked -- | Not enough arguments were supplied to complete the matching. Underapplied :: NotBlocked -- | We matched an absurd clause, results in a neutral Def. AbsurdMatch :: NotBlocked -- | We ran out of clauses, all considered clauses produced an actual -- mismatch. This can happen when try to reduce a function application -- but we are still missing some function clauses. See -- Agda.TypeChecking.Patterns.Match. MissingClauses :: NotBlocked -- | Reduction was not blocked, we reached a whnf which can be anything but -- a stuck Def. ReallyNotBlocked :: NotBlocked -- | ReallyNotBlocked is the unit. MissingClauses is -- dominant. StuckOn{} should be propagated, if tied, we -- take the left. -- | Something where a meta variable may block reduction. data Blocked t Blocked :: MetaId -> t -> Blocked t [theBlockingMeta] :: Blocked t -> MetaId [ignoreBlocking] :: Blocked t -> t NotBlocked :: NotBlocked -> t -> Blocked t [blockingStatus] :: Blocked t -> NotBlocked [ignoreBlocking] :: Blocked t -> t -- | Blocking by a meta is dominant. -- | Blocked t without the t. type Blocked_ = Blocked () -- | When trying to reduce f es, on match failed on one -- elimination e ∈ es that came with info r :: -- NotBlocked. stuckOn e r produces the new -- NotBlocked info. -- -- MissingClauses must be propagated, as this is blockage that can -- be lifted in the future (as more clauses are added). -- -- StuckOn e0 is also propagated, since it provides more -- precise information as StuckOn e (as e0 is the -- original reason why reduction got stuck and usually a subterm of -- e). An information like StuckOn (Apply (Arg info (Var i -- []))) (stuck on a variable) could be used by the lhs/coverage -- checker to trigger a split on that (pattern) variable. -- -- In the remaining cases for r, we are terminally stuck due to -- StuckOn e. Propagating AbsurdMatch does not -- seem useful. -- -- Underapplied must not be propagated, as this would mean that -- f es is underapplied, which is not the case (it is stuck). -- Note that Underapplied can only arise when projection patterns -- were missing to complete the original match (in e). (Missing -- ordinary pattern would mean the e is of function type, but we -- cannot match against something of function type.) stuckOn :: Elim -> NotBlocked -> NotBlocked -- | A clause is a list of patterns and the clause body should -- Bind. -- -- The telescope contains the types of the pattern variables and the -- permutation is how to get from the order the variables occur in the -- patterns to the order they occur in the telescope. The body binds the -- variables in the order they appear in the patterns. -- --
--   clauseTel ~ permute clausePerm (patternVars namedClausePats)
--   
-- -- Terms in dot patterns are valid in the clause telescope. -- -- For the purpose of the permutation and the body dot patterns count as -- variables. TODO: Change this! data Clause Clause :: Range -> Telescope -> Permutation -> [NamedArg Pattern] -> ClauseBody -> Maybe (Arg Type) -> Clause [clauseRange] :: Clause -> Range -- | Δ: The types of the pattern variables. [clauseTel] :: Clause -> Telescope -- | π with Γ ⊢ renamingR π : Δ, which means Δ ⊢ -- renaming π : Γ. [clausePerm] :: Clause -> Permutation -- |
--   let Γ = patternVars namedClausePats
--   
[namedClausePats] :: Clause -> [NamedArg Pattern] -- |
--   λΓ.v
--   
[clauseBody] :: Clause -> ClauseBody -- | Δ ⊢ t. The type of the rhs under clauseTel. Used, -- e.g., by TermCheck. Can be Irrelevant if we -- encountered an irrelevant projection pattern on the lhs. [clauseType] :: Clause -> Maybe (Arg Type) clausePats :: Clause -> [Arg Pattern] data ClauseBodyF a Body :: a -> ClauseBodyF a Bind :: (Abs (ClauseBodyF a)) -> ClauseBodyF a -- | for absurd clauses. NoBody :: ClauseBodyF a type ClauseBody = ClauseBodyF Term imapClauseBody :: (Nat -> a -> b) -> ClauseBodyF a -> ClauseBodyF b -- | Pattern variables. type PatVarName = ArgName patVarNameToString :: PatVarName -> String nameToPatVarName :: Name -> PatVarName -- | Patterns are variables, constructors, or wildcards. QName is -- used in ConP rather than Name since a constructor -- might come from a particular namespace. This also meshes well with the -- fact that values (i.e. the arguments we are matching with) use -- QName. data Pattern' x -- |
--   x
--   
VarP :: x -> Pattern' x -- |
--   .t
--   
DotP :: Term -> Pattern' x -- | c ps The subpatterns do not contain any projection -- copatterns. ConP :: ConHead -> ConPatternInfo -> [NamedArg (Pattern' x)] -> Pattern' x -- | E.g. 5, "hello". LitP :: Literal -> Pattern' x -- | Projection copattern. Can only appear by itself. ProjP :: QName -> Pattern' x type Pattern = Pattern' PatVarName The @PatVarName@ is a name suggestion. -- | Type used when numbering pattern variables. type DeBruijnPattern = Pattern' (Int, PatVarName) namedVarP :: PatVarName -> Named (Ranged PatVarName) Pattern -- | The ConPatternInfo states whether the constructor belongs to -- a record type (Just) or data type (Nothing). In the -- former case, the Bool says whether the record pattern -- orginates from the expansion of an implicit pattern. The Type -- is the type of the whole record pattern. The scope used for the type -- is given by any outer scope plus the clause's telescope -- (clauseTel). data ConPatternInfo ConPatternInfo :: Maybe ConPOrigin -> Maybe (Arg Type) -> ConPatternInfo -- | Nothing if data constructor. Just if record -- constructor. [conPRecord] :: ConPatternInfo -> Maybe ConPOrigin -- | The type of the whole constructor pattern. Should be present -- (Just) if constructor pattern is is generated ordinarily by -- type-checking. Could be absent (Nothing) if pattern comes -- from some plugin (like Agsy). Needed e.g. for with-clause stripping. [conPType] :: ConPatternInfo -> Maybe (Arg Type) noConPatternInfo :: ConPatternInfo -- | Extract pattern variables in left-to-right order. A DotP is -- also treated as variable (see docu for Clause). patternVars :: Arg Pattern -> [Arg (Either PatVarName Term)] -- | Does the pattern perform a match that could fail? properlyMatching :: Pattern -> Bool -- | Substitutions. data Substitution -- | Identity substitution. Γ ⊢ IdS : Γ IdS :: Substitution -- | Empty substitution, lifts from the empty context. Apply this to closed -- terms you want to use in a non-empty context. Γ ⊢ EmptyS : () EmptyS :: Substitution -- | Substitution extension, `cons'. Γ ⊢ u : Aρ Γ ⊢ ρ : Δ -- ---------------------- Γ ⊢ u :# ρ : Δ, A (:#) :: Term -> Substitution -> Substitution -- | Strengthening substitution. First argument is -- IMPOSSIBLE. Apply this to a term which does not -- contain variable 0 to lower all de Bruijn indices by one. Γ ⊢ ρ : -- Δ --------------------------- Γ ⊢ Strengthen ρ : Δ, A Strengthen :: Empty -> Substitution -> Substitution -- | Weakning substitution, lifts to an extended context. Γ ⊢ ρ : Δ -- ------------------- Γ, Ψ ⊢ Wk |Ψ| ρ : Δ Wk :: !Int -> Substitution -> Substitution -- | Lifting substitution. Use this to go under a binder. Lift 1 ρ == -- var 0 :# Wk 1 ρ. Γ ⊢ ρ : Δ ------------------------- Γ, Ψρ ⊢ -- Lift |Ψ| ρ : Δ, Ψ Lift :: !Int -> Substitution -> Substitution -- | Absurd lambdas are internally represented as identity with variable -- name "()". absurdBody :: Abs Term isAbsurdBody :: Abs Term -> Bool absurdPatternName :: PatVarName isAbsurdPatternName :: PatVarName -> Bool ignoreSharing :: Term -> Term ignoreSharingType :: Type -> Type -- | Introduce sharing. shared :: Term -> Term sharedType :: Type -> Type -- | Typically m would be TCM and f would be Blocked. updateSharedFM :: (Monad m, Applicative m, Traversable f) => (Term -> m (f Term)) -> Term -> m (f Term) updateSharedM :: Monad m => (Term -> m Term) -> Term -> m Term updateShared :: (Term -> Term) -> Term -> Term pointerChain :: Term -> [Ptr Term] compressPointerChain :: Term -> Term -- | An unapplied variable. var :: Nat -> Term -- | Add DontCare is it is not already a DontCare. dontCare :: Term -> Term -- | A dummy type. typeDontCare :: Type -- | Top sort (Setomega). topSort :: Type sort :: Sort -> Type varSort :: Int -> Sort -- | Get the next higher sort. sSuc :: Sort -> Sort levelSuc :: Level -> Level mkType :: Integer -> Sort impossibleTerm :: String -> Int -> Term -- | Constructing a singleton telescope. class SgTel a sgTel :: SgTel a => a -> Telescope hackReifyToMeta :: Term isHackReifyToMeta :: Term -> Bool blockingMeta :: Blocked t -> Maybe MetaId blocked :: MetaId -> a -> Blocked a notBlocked :: a -> Blocked a -- | Removing a topmost DontCare constructor. stripDontCare :: Term -> Term -- | Doesn't do any reduction. arity :: Type -> Nat -- | Make a name that is not in scope. notInScopeName :: ArgName -> ArgName -- | Pick the better name suggestion, i.e., the one that is not just -- underscore. class Suggest a b suggest :: Suggest a b => a -> b -> String -- | Convert top-level postfix projections into prefix projections. unSpine :: Term -> Term -- | A view distinguishing the neutrals Var, Def, and -- MetaV which can be projected. hasElims :: Term -> Maybe (Elims -> Term, Elims) -- | Drop Apply constructor. (Unsafe!) argFromElim :: Elim -> Arg Term -- | Drop Apply constructor. (Safe) isApplyElim :: Elim -> Maybe (Arg Term) -- | Drop Apply constructors. (Safe) allApplyElims :: Elims -> Maybe Args -- | Split at first non-Apply splitApplyElims :: Elims -> (Args, Elims) class IsProjElim e isProjElim :: IsProjElim e => e -> Maybe QName -- | Discard Proj f entries. dropProjElims :: IsProjElim e => [e] -> [e] -- | Discards Proj f entries. argsFromElims :: Elims -> Args -- | A null clause is one with no patterns and no rhs. Should not -- exist in practice. -- | The size of a telescope is its length (as a list). -- | The size of a term is roughly the number of nodes in its syntax tree. -- This number need not be precise for logical correctness of Agda, it is -- only used for reporting (and maybe decisions regarding performance). -- -- Not counting towards the term size are: -- -- class TermSize a where termSize = getSum . tsize termSize :: TermSize a => a -> Int tsize :: TermSize a => a -> Sum Int -- | A meta variable identifier is just a natural number. newtype MetaId MetaId :: Nat -> MetaId [metaId] :: MetaId -> Nat instance Data.Generics.Geniplate.UniverseBi [Agda.Syntax.Internal.Term] Agda.Syntax.Internal.Term instance Agda.Utils.Pretty.Pretty Agda.Syntax.Internal.Substitution instance Agda.Utils.Pretty.Pretty Agda.Syntax.Internal.Term instance Agda.Utils.Pretty.Pretty Agda.Syntax.Internal.Level instance Agda.Utils.Pretty.Pretty Agda.Syntax.Internal.PlusLevel instance Agda.Utils.Pretty.Pretty Agda.Syntax.Internal.LevelAtom instance Agda.Utils.Pretty.Pretty Agda.Syntax.Internal.Sort instance Agda.Utils.Pretty.Pretty Agda.Syntax.Internal.Type instance Agda.Utils.Pretty.Pretty Agda.Syntax.Internal.Elim instance Agda.Utils.Pretty.Pretty a => Agda.Utils.Pretty.Pretty (Agda.Syntax.Internal.Arg a) instance Agda.Utils.Pretty.Pretty a => Agda.Utils.Pretty.Pretty (Agda.Syntax.Internal.Pattern' a) instance Agda.Utils.Pretty.Pretty a => Agda.Utils.Pretty.Pretty (Agda.Syntax.Internal.ClauseBodyF a) instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Internal.Elims Agda.Syntax.Internal.Term instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Internal.Args Agda.Syntax.Internal.Term instance Data.Generics.Geniplate.UniverseBi ([Agda.Syntax.Internal.Type], [Agda.Syntax.Internal.Clause]) Agda.Syntax.Internal.Term instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Internal.Elims Agda.Syntax.Internal.Pattern instance Data.Generics.Geniplate.UniverseBi Agda.Syntax.Internal.Args Agda.Syntax.Internal.Pattern instance Data.Generics.Geniplate.UniverseBi ([Agda.Syntax.Internal.Type], [Agda.Syntax.Internal.Clause]) Agda.Syntax.Internal.Pattern instance GHC.Show.Show Agda.Syntax.Internal.Substitution instance Data.Traversable.Traversable Agda.Syntax.Internal.Blocked instance Data.Foldable.Foldable Agda.Syntax.Internal.Blocked instance GHC.Base.Functor Agda.Syntax.Internal.Blocked instance GHC.Show.Show t => GHC.Show.Show (Agda.Syntax.Internal.Blocked t) instance Data.Traversable.Traversable Agda.Syntax.Internal.Pattern' instance Data.Foldable.Foldable Agda.Syntax.Internal.Pattern' instance GHC.Base.Functor Agda.Syntax.Internal.Pattern' instance GHC.Show.Show x => GHC.Show.Show (Agda.Syntax.Internal.Pattern' x) instance GHC.Show.Show Agda.Syntax.Internal.Clause instance GHC.Show.Show Agda.Syntax.Internal.Term instance Data.Traversable.Traversable Agda.Syntax.Internal.Elim' instance Data.Foldable.Foldable Agda.Syntax.Internal.Elim' instance GHC.Base.Functor Agda.Syntax.Internal.Elim' instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Internal.Elim' a) instance GHC.Show.Show Agda.Syntax.Internal.NotBlocked instance GHC.Show.Show Agda.Syntax.Internal.LevelAtom instance GHC.Show.Show Agda.Syntax.Internal.PlusLevel instance GHC.Show.Show Agda.Syntax.Internal.Level instance GHC.Show.Show Agda.Syntax.Internal.Sort instance Data.Traversable.Traversable Agda.Syntax.Internal.Type' instance Data.Foldable.Foldable Agda.Syntax.Internal.Type' instance GHC.Base.Functor Agda.Syntax.Internal.Type' instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Internal.Type' a) instance GHC.Show.Show Agda.Syntax.Internal.ConPatternInfo instance Data.Traversable.Traversable Agda.Syntax.Internal.ClauseBodyF instance Data.Foldable.Foldable Agda.Syntax.Internal.ClauseBodyF instance GHC.Base.Functor Agda.Syntax.Internal.ClauseBodyF instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Internal.ClauseBodyF a) instance Data.Traversable.Traversable Agda.Syntax.Internal.Tele instance Data.Foldable.Foldable Agda.Syntax.Internal.Tele instance GHC.Base.Functor Agda.Syntax.Internal.Tele instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Internal.Tele a) instance Data.Traversable.Traversable Agda.Syntax.Internal.Abs instance Data.Foldable.Foldable Agda.Syntax.Internal.Abs instance GHC.Base.Functor Agda.Syntax.Internal.Abs instance GHC.Classes.Eq Agda.Syntax.Internal.ConHead instance GHC.Classes.Ord Agda.Syntax.Internal.ConHead instance GHC.Show.Show Agda.Syntax.Internal.ConHead instance Agda.Syntax.Position.HasRange Agda.Syntax.Internal.ConHead instance Agda.Syntax.Position.SetRange Agda.Syntax.Internal.ConHead instance Agda.Syntax.Internal.LensConName Agda.Syntax.Internal.ConHead instance Agda.Utils.Functor.Decoration Agda.Syntax.Internal.Abs instance Agda.Utils.Functor.Decoration Agda.Syntax.Internal.Type' instance Agda.Syntax.Internal.LensSort (Agda.Syntax.Internal.Type' a) instance Agda.Syntax.Internal.LensSort a => Agda.Syntax.Internal.LensSort (Agda.Syntax.Common.Dom c a) instance Agda.Syntax.Internal.LensSort a => Agda.Syntax.Internal.LensSort (Agda.Syntax.Internal.Abs a) instance GHC.Base.Monoid Agda.Syntax.Internal.NotBlocked instance GHC.Base.Applicative Agda.Syntax.Internal.Blocked instance GHC.Base.Monoid Agda.Syntax.Internal.Blocked_ instance Agda.Syntax.Position.HasRange Agda.Syntax.Internal.Clause instance Agda.Syntax.Abstract.IsProjP Agda.Syntax.Internal.Pattern instance Agda.Syntax.Internal.SgTel (Agda.Syntax.Internal.ArgName, Agda.Syntax.Internal.Dom Agda.Syntax.Internal.Type) instance Agda.Syntax.Internal.SgTel (Agda.Syntax.Internal.Dom (Agda.Syntax.Internal.ArgName, Agda.Syntax.Internal.Type)) instance Agda.Syntax.Internal.SgTel (Agda.Syntax.Internal.Dom Agda.Syntax.Internal.Type) instance Agda.Syntax.Internal.Suggest GHC.Base.String GHC.Base.String instance Agda.Syntax.Internal.Suggest (Agda.Syntax.Internal.Abs a) (Agda.Syntax.Internal.Abs b) instance Agda.Syntax.Internal.Suggest GHC.Base.String (Agda.Syntax.Internal.Abs b) instance Agda.Syntax.Internal.Suggest Agda.Syntax.Abstract.Name.Name (Agda.Syntax.Internal.Abs b) instance Agda.Syntax.Internal.IsProjElim Agda.Syntax.Internal.Elim instance Agda.Utils.Null.Null (Agda.Syntax.Internal.Tele a) instance Agda.Utils.Null.Null Agda.Syntax.Internal.ClauseBody instance Agda.Utils.Null.Null Agda.Syntax.Internal.Clause instance GHC.Show.Show a => GHC.Show.Show (Agda.Syntax.Internal.Abs a) instance Agda.Utils.Size.Sized (Agda.Syntax.Internal.Tele a) instance Agda.Utils.Size.Sized a => Agda.Utils.Size.Sized (Agda.Syntax.Internal.Abs a) instance (Data.Foldable.Foldable t, Agda.Syntax.Internal.TermSize a) => Agda.Syntax.Internal.TermSize (t a) instance Agda.Syntax.Internal.TermSize Agda.Syntax.Internal.Term instance Agda.Syntax.Internal.TermSize Agda.Syntax.Internal.Sort instance Agda.Syntax.Internal.TermSize Agda.Syntax.Internal.Level instance Agda.Syntax.Internal.TermSize Agda.Syntax.Internal.PlusLevel instance Agda.Syntax.Internal.TermSize Agda.Syntax.Internal.LevelAtom instance Agda.Syntax.Internal.TermSize Agda.Syntax.Internal.Substitution instance Agda.Syntax.Position.KillRange Agda.Syntax.Internal.ConHead instance Agda.Syntax.Position.KillRange Agda.Syntax.Internal.Term instance Agda.Syntax.Position.KillRange Agda.Syntax.Internal.Level instance Agda.Syntax.Position.KillRange Agda.Syntax.Internal.PlusLevel instance Agda.Syntax.Position.KillRange Agda.Syntax.Internal.LevelAtom instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Agda.Syntax.Internal.Type' a) instance Agda.Syntax.Position.KillRange Agda.Syntax.Internal.Sort instance Agda.Syntax.Position.KillRange Agda.Syntax.Internal.Substitution instance Agda.Syntax.Position.KillRange Agda.Syntax.Internal.ConPatternInfo instance Agda.Syntax.Position.KillRange Agda.Syntax.Internal.Pattern instance Agda.Syntax.Position.KillRange Agda.Syntax.Internal.Clause instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Agda.Syntax.Internal.ClauseBodyF a) instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Agda.Syntax.Internal.Tele a) instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Agda.Syntax.Internal.Blocked a) instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Agda.Syntax.Internal.Abs a) instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Agda.Syntax.Internal.Elim' a) -- | Epic interface data structure, which is serialisable and stored for -- each compiled file module Agda.Compiler.Epic.Interface type Var = String data Tag Tag :: Int -> Tag PrimTag :: Var -> Tag data Forced NotForced :: Forced Forced :: Forced -- | Filter a list using a list of Bools specifying what to keep. pairwiseFilter :: [Bool] -> [a] -> [a] notForced :: ForcedArgs -> [a] -> [a] forced :: ForcedArgs -> [a] -> [a] data Relevance Irr :: Relevance Rel :: Relevance type ForcedArgs = [Forced] type RelevantArgs = [Relevance] data InjectiveFun InjectiveFun :: Nat -> Nat -> InjectiveFun [injArg] :: InjectiveFun -> Nat [injArity] :: InjectiveFun -> Nat data EInterface EInterface :: Map QName Tag -> Set Var -> Map QName Bool -> Map QName Int -> Maybe QName -> Map Var RelevantArgs -> Map QName ForcedArgs -> Map QName InjectiveFun -> EInterface [constrTags] :: EInterface -> Map QName Tag [definitions] :: EInterface -> Set Var [defDelayed] :: EInterface -> Map QName Bool [conArity] :: EInterface -> Map QName Int [mainName] :: EInterface -> Maybe QName [relevantArgs] :: EInterface -> Map Var RelevantArgs [forcedArgs] :: EInterface -> Map QName ForcedArgs [injectiveFuns] :: EInterface -> Map QName InjectiveFun instance GHC.Show.Show Agda.Compiler.Epic.Interface.EInterface instance GHC.Classes.Eq Agda.Compiler.Epic.Interface.InjectiveFun instance GHC.Show.Show Agda.Compiler.Epic.Interface.InjectiveFun instance GHC.Show.Show Agda.Compiler.Epic.Interface.Relevance instance GHC.Classes.Ord Agda.Compiler.Epic.Interface.Relevance instance GHC.Classes.Eq Agda.Compiler.Epic.Interface.Relevance instance GHC.Classes.Eq Agda.Compiler.Epic.Interface.Forced instance GHC.Show.Show Agda.Compiler.Epic.Interface.Forced instance GHC.Classes.Ord Agda.Compiler.Epic.Interface.Tag instance GHC.Classes.Eq Agda.Compiler.Epic.Interface.Tag instance GHC.Show.Show Agda.Compiler.Epic.Interface.Tag instance GHC.Base.Monoid Agda.Compiler.Epic.Interface.EInterface -- | Intermediate abstract syntax tree used in the compiler. Pretty close -- to Epic syntax. module Agda.Compiler.Epic.AuxAST type Comment = String type Inline = Bool data Fun Fun :: Inline -> Var -> Maybe QName -> Comment -> [Var] -> Expr -> Fun [funInline] :: Fun -> Inline [funName] :: Fun -> Var [funQName] :: Fun -> Maybe QName [funComment] :: Fun -> Comment [funArgs] :: Fun -> [Var] [funExpr] :: Fun -> Expr EpicFun :: Var -> Maybe QName -> Comment -> String -> Fun [funName] :: Fun -> Var [funQName] :: Fun -> Maybe QName [funComment] :: Fun -> Comment [funEpicCode] :: Fun -> String data Lit LInt :: Integer -> Lit LChar :: Char -> Lit LString :: String -> Lit LFloat :: Double -> Lit data Expr Var :: Var -> Expr Lit :: Lit -> Expr Lam :: Var -> Expr -> Expr Con :: Tag -> QName -> [Expr] -> Expr App :: Var -> [Expr] -> Expr Case :: Expr -> [Branch] -> Expr If :: Expr -> Expr -> Expr -> Expr Let :: Var -> Expr -> Expr -> Expr Lazy :: Expr -> Expr UNIT :: Expr IMPOSSIBLE :: Expr data Branch Branch :: Tag -> QName -> [Var] -> Expr -> Branch [brTag] :: Branch -> Tag [brName] :: Branch -> QName [brVars] :: Branch -> [Var] [brExpr] :: Branch -> Expr BrInt :: Int -> Expr -> Branch [brInt] :: Branch -> Int [brExpr] :: Branch -> Expr Default :: Expr -> Branch [brExpr] :: Branch -> Expr getBrVars :: Branch -> [Var] -- | Smart constructor for let expressions to avoid unneceessary lets lett :: Var -> Expr -> Expr -> Expr -- | Some things are pointless to make lazy lazy :: Expr -> Expr -- | If casing on the same expression in a sub-expression, we know what -- branch to pick casee :: Expr -> [Branch] -> Expr -- | Smart constructor for applications to avoid empty applications apps :: Var -> [Expr] -> Expr -- | Substitution subst :: Var -> Var -> Expr -> Expr substs :: [(Var, Var)] -> Expr -> Expr substBranch :: Var -> Var -> Branch -> Branch -- | Get the free variables in an expression fv :: Expr -> [Var] instance GHC.Show.Show Agda.Compiler.Epic.AuxAST.Fun instance GHC.Classes.Ord Agda.Compiler.Epic.AuxAST.Fun instance GHC.Classes.Eq Agda.Compiler.Epic.AuxAST.Fun instance GHC.Classes.Eq Agda.Compiler.Epic.AuxAST.Expr instance GHC.Classes.Ord Agda.Compiler.Epic.AuxAST.Expr instance GHC.Show.Show Agda.Compiler.Epic.AuxAST.Expr instance GHC.Classes.Eq Agda.Compiler.Epic.AuxAST.Branch instance GHC.Classes.Ord Agda.Compiler.Epic.AuxAST.Branch instance GHC.Show.Show Agda.Compiler.Epic.AuxAST.Branch instance GHC.Classes.Eq Agda.Compiler.Epic.AuxAST.Lit instance GHC.Classes.Ord Agda.Compiler.Epic.AuxAST.Lit instance GHC.Show.Show Agda.Compiler.Epic.AuxAST.Lit -- | Case trees. -- -- After coverage checking, pattern matching is translated to case trees, -- i.e., a tree of successive case splits on one variable at a time. module Agda.TypeChecking.CompiledClause data WithArity c WithArity :: Int -> c -> WithArity c [arity] :: WithArity c -> Int [content] :: WithArity c -> c -- | Branches in a case tree. data Case c Branches :: Bool -> Map QName (WithArity c) -> Map Literal c -> Maybe c -> Case c -- | We are constructing a record here (copatterns). conBranches -- lists projections. [projPatterns] :: Case c -> Bool -- | Map from constructor (or projection) names to their arity and the case -- subtree. (Projections have arity 0.) [conBranches] :: Case c -> Map QName (WithArity c) -- | Map from literal to case subtree. [litBranches] :: Case c -> Map Literal c -- | (Possibly additional) catch-all clause. [catchAllBranch] :: Case c -> Maybe c -- | Case tree with bodies. data CompiledClauses -- | Case n bs stands for a match on the n-th argument -- (counting from zero) with bs as the case branches. If the -- n-th argument is a projection, we have only -- conBranches with arity 0. Case :: Int -> (Case CompiledClauses) -> CompiledClauses -- | Done xs b stands for the body b where the -- xs contains hiding and name suggestions for the free -- variables. This is needed to build lambdas on the right hand side for -- partial applications which can still reduce. Done :: [Arg ArgName] -> Term -> CompiledClauses -- | Absurd case. Fail :: CompiledClauses litCase :: Literal -> c -> Case c conCase :: QName -> WithArity c -> Case c projCase :: QName -> c -> Case c catchAll :: c -> Case c -- | Check whether a case tree has a catch-all clause. hasCatchAll :: CompiledClauses -> Bool prettyMap :: (Show k, Pretty v) => Map k v -> [Doc] instance Data.Traversable.Traversable Agda.TypeChecking.CompiledClause.Case instance Data.Foldable.Foldable Agda.TypeChecking.CompiledClause.Case instance GHC.Base.Functor Agda.TypeChecking.CompiledClause.Case instance Data.Traversable.Traversable Agda.TypeChecking.CompiledClause.WithArity instance Data.Foldable.Foldable Agda.TypeChecking.CompiledClause.WithArity instance GHC.Base.Functor Agda.TypeChecking.CompiledClause.WithArity instance GHC.Base.Monoid c => GHC.Base.Monoid (Agda.TypeChecking.CompiledClause.WithArity c) instance GHC.Base.Monoid m => GHC.Base.Monoid (Agda.TypeChecking.CompiledClause.Case m) instance Agda.Utils.Null.Null (Agda.TypeChecking.CompiledClause.Case m) instance Agda.Utils.Pretty.Pretty a => GHC.Show.Show (Agda.TypeChecking.CompiledClause.Case a) instance GHC.Show.Show Agda.TypeChecking.CompiledClause.CompiledClauses instance Agda.Utils.Pretty.Pretty a => Agda.Utils.Pretty.Pretty (Agda.TypeChecking.CompiledClause.WithArity a) instance Agda.Utils.Pretty.Pretty a => Agda.Utils.Pretty.Pretty (Agda.TypeChecking.CompiledClause.Case a) instance Agda.Utils.Pretty.Pretty Agda.TypeChecking.CompiledClause.CompiledClauses instance Agda.Syntax.Position.KillRange c => Agda.Syntax.Position.KillRange (Agda.TypeChecking.CompiledClause.WithArity c) instance Agda.Syntax.Position.KillRange c => Agda.Syntax.Position.KillRange (Agda.TypeChecking.CompiledClause.Case c) instance Agda.Syntax.Position.KillRange Agda.TypeChecking.CompiledClause.CompiledClauses -- | Extract used definitions from terms. module Agda.Syntax.Internal.Defs -- | getDefs' lookup emb a extracts all used definitions -- (functions, data/record types) from a, embedded into a monoid -- via emb. Instantiations of meta variables are obtained via -- lookup. -- -- Typical monoid instances would be [QName] or Set -- QName. Note that emb can also choose to discard a used -- definition by mapping to the unit of the monoid. getDefs' :: (GetDefs a, Monoid b) => (MetaId -> Maybe Term) -> (QName -> b) -> a -> b -- | Inputs to and outputs of getDefs' are organized as a monad. type GetDefsM b = ReaderT (GetDefsEnv b) (Writer b) data GetDefsEnv b GetDefsEnv :: (MetaId -> Maybe Term) -> (QName -> b) -> GetDefsEnv b [lookupMeta] :: GetDefsEnv b -> MetaId -> Maybe Term [embDef] :: GetDefsEnv b -> QName -> b -- | What it takes to get the used definitions. class Monad m => MonadGetDefs m doDef :: MonadGetDefs m => QName -> m () doMeta :: MonadGetDefs m => MetaId -> m () -- | Getting the used definitions. class GetDefs a getDefs :: (GetDefs a, MonadGetDefs m) => a -> m () instance GHC.Base.Monoid b => Agda.Syntax.Internal.Defs.MonadGetDefs (Agda.Syntax.Internal.Defs.GetDefsM b) instance Agda.Syntax.Internal.Defs.GetDefs Agda.Syntax.Internal.Clause instance Agda.Syntax.Internal.Defs.GetDefs Agda.Syntax.Internal.ClauseBody instance Agda.Syntax.Internal.Defs.GetDefs Agda.Syntax.Internal.Term instance Agda.Syntax.Internal.Defs.GetDefs Agda.Syntax.Common.MetaId instance Agda.Syntax.Internal.Defs.GetDefs Agda.Syntax.Internal.Type instance Agda.Syntax.Internal.Defs.GetDefs Agda.Syntax.Internal.Sort instance Agda.Syntax.Internal.Defs.GetDefs Agda.Syntax.Internal.Level instance Agda.Syntax.Internal.Defs.GetDefs Agda.Syntax.Internal.PlusLevel instance Agda.Syntax.Internal.Defs.GetDefs Agda.Syntax.Internal.LevelAtom instance Agda.Syntax.Internal.Defs.GetDefs a => Agda.Syntax.Internal.Defs.GetDefs (GHC.Base.Maybe a) instance Agda.Syntax.Internal.Defs.GetDefs a => Agda.Syntax.Internal.Defs.GetDefs [a] instance Agda.Syntax.Internal.Defs.GetDefs a => Agda.Syntax.Internal.Defs.GetDefs (Agda.Syntax.Internal.Elim' a) instance Agda.Syntax.Internal.Defs.GetDefs c => Agda.Syntax.Internal.Defs.GetDefs (Agda.Syntax.Common.ArgInfo c) instance (Agda.Syntax.Internal.Defs.GetDefs c, Agda.Syntax.Internal.Defs.GetDefs a) => Agda.Syntax.Internal.Defs.GetDefs (Agda.Syntax.Common.Arg c a) instance (Agda.Syntax.Internal.Defs.GetDefs c, Agda.Syntax.Internal.Defs.GetDefs a) => Agda.Syntax.Internal.Defs.GetDefs (Agda.Syntax.Common.Dom c a) instance Agda.Syntax.Internal.Defs.GetDefs a => Agda.Syntax.Internal.Defs.GetDefs (Agda.Syntax.Internal.Abs a) instance (Agda.Syntax.Internal.Defs.GetDefs a, Agda.Syntax.Internal.Defs.GetDefs b) => Agda.Syntax.Internal.Defs.GetDefs (a, b) module Agda.Syntax.Internal.Generic class TermLike a traverseTerm :: TermLike a => (Term -> Term) -> a -> a traverseTermM :: (TermLike a, Monad m, Applicative m) => (Term -> m Term) -> a -> m a foldTerm :: (TermLike a, Monoid m) => (Term -> m) -> a -> m -- | Put it in a monad to make it possible to do strictly. copyTerm :: (TermLike a, Applicative m, Monad m) => a -> m a instance Agda.Syntax.Internal.Generic.TermLike GHC.Types.Bool instance Agda.Syntax.Internal.Generic.TermLike GHC.Types.Int instance Agda.Syntax.Internal.Generic.TermLike GHC.Integer.Type.Integer instance Agda.Syntax.Internal.Generic.TermLike GHC.Types.Char instance Agda.Syntax.Internal.Generic.TermLike Agda.Syntax.Abstract.Name.QName instance Agda.Syntax.Internal.Generic.TermLike a => Agda.Syntax.Internal.Generic.TermLike (Agda.Syntax.Internal.Elim' a) instance Agda.Syntax.Internal.Generic.TermLike a => Agda.Syntax.Internal.Generic.TermLike (Agda.Syntax.Internal.Arg a) instance Agda.Syntax.Internal.Generic.TermLike a => Agda.Syntax.Internal.Generic.TermLike (Agda.Syntax.Internal.Dom a) instance Agda.Syntax.Internal.Generic.TermLike a => Agda.Syntax.Internal.Generic.TermLike [a] instance Agda.Syntax.Internal.Generic.TermLike a => Agda.Syntax.Internal.Generic.TermLike (GHC.Base.Maybe a) instance (Agda.Syntax.Internal.Generic.TermLike a, Agda.Syntax.Internal.Generic.TermLike b) => Agda.Syntax.Internal.Generic.TermLike (a, b) instance (Agda.Syntax.Internal.Generic.TermLike a, Agda.Syntax.Internal.Generic.TermLike b, Agda.Syntax.Internal.Generic.TermLike c) => Agda.Syntax.Internal.Generic.TermLike (a, b, c) instance (Agda.Syntax.Internal.Generic.TermLike a, Agda.Syntax.Internal.Generic.TermLike b, Agda.Syntax.Internal.Generic.TermLike c, Agda.Syntax.Internal.Generic.TermLike d) => Agda.Syntax.Internal.Generic.TermLike (a, b, c, d) instance Agda.Syntax.Internal.Generic.TermLike a => Agda.Syntax.Internal.Generic.TermLike (Agda.Syntax.Internal.Abs a) instance Agda.Syntax.Internal.Generic.TermLike a => Agda.Syntax.Internal.Generic.TermLike (Agda.Utils.Pointer.Ptr a) instance Agda.Syntax.Internal.Generic.TermLike Agda.Syntax.Internal.Term instance Agda.Syntax.Internal.Generic.TermLike Agda.Syntax.Internal.Level instance Agda.Syntax.Internal.Generic.TermLike Agda.Syntax.Internal.PlusLevel instance Agda.Syntax.Internal.Generic.TermLike Agda.Syntax.Internal.LevelAtom instance Agda.Syntax.Internal.Generic.TermLike Agda.Syntax.Internal.Type -- | Computing the free variables of a term lazily. -- -- We implement a reduce (traversal into monoid) over internal syntax for -- a generic collection (monoid with singletons). This should allow a -- more efficient test for the presence of a particular variable. -- -- Worst-case complexity does not change (i.e. the case when a variable -- does not occur), but best case-complexity does matter. For instance, -- see mkAbs: each time we construct a dependent function type, we -- check it is actually dependent. -- -- The distinction between rigid and strongly rigid occurrences comes -- from: Jason C. Reed, PhD thesis, 2009, page 96 (see also his LFMTP -- 2009 paper) -- -- The main idea is that x = t(x) is unsolvable if x occurs strongly -- rigidly in t. It might have a solution if the occurrence is not -- strongly rigid, e.g. -- -- x = f -> suc (f (x ( y -> k))) has x = f -> suc (f (suc k)) -- -- -- -- Under coinductive constructors, occurrences are never strongly rigid. -- Also, function types and lambdas do not establish strong rigidity. -- Only inductive constructors do so. (See issue 1271). module Agda.TypeChecking.Free.Lazy -- | Depending on the surrounding context of a variable, it's occurrence -- can be classified as flexible or rigid, with finer distinctions. -- -- The constructors are listed in increasing order (wrt. information -- content). data FlexRig -- | In arguments of metas. Flexible :: FlexRig -- | In arguments to variables and definitions. WeaklyRigid :: FlexRig -- | In top position, or only under inductive record constructors. Unguarded :: FlexRig -- | Under at least one and only inductive constructors. StronglyRigid :: FlexRig -- | FlexRig composition. For accumulating the context of a -- variable. -- -- Flexible is dominant. Once we are under a meta, we are flexible -- regardless what else comes. -- -- WeaklyRigid is next in strength. Destroys strong rigidity. -- -- StronglyRigid is still dominant over Unguarded. -- -- Unguarded is the unit. It is the top (identity) context. composeFlexRig :: FlexRig -> FlexRig -> FlexRig -- | Occurrence of free variables is classified by several dimensions. -- Currently, we have FlexRig and Relevance. data VarOcc VarOcc :: FlexRig -> Relevance -> VarOcc [varFlexRig] :: VarOcc -> FlexRig [varRelevance] :: VarOcc -> Relevance -- | When we extract information about occurrence, we care most about about -- StronglyRigid Relevant occurrences. maxVarOcc :: VarOcc -> VarOcc -> VarOcc topVarOcc :: VarOcc botVarOcc :: VarOcc type VarMap = IntMap VarOcc -- | Where should we skip sorts in free variable analysis? data IgnoreSorts -- | Do not skip. IgnoreNot :: IgnoreSorts -- | Skip when annotation to a type. IgnoreInAnnotations :: IgnoreSorts -- | Skip unconditionally. IgnoreAll :: IgnoreSorts -- | The current context. data FreeEnv c FreeEnv :: !IgnoreSorts -> !Int -> !FlexRig -> !Relevance -> SingleVar c -> FreeEnv c -- | Ignore free variables in sorts. [feIgnoreSorts] :: FreeEnv c -> !IgnoreSorts -- | Under how many binders have we stepped? [feBinders] :: FreeEnv c -> !Int -- | Are we flexible or rigid? [feFlexRig] :: FreeEnv c -> !FlexRig -- | What is the current relevance? [feRelevance] :: FreeEnv c -> !Relevance -- | Method to return a single variable. [feSingleton] :: FreeEnv c -> SingleVar c type Variable = (Int, VarOcc) type SingleVar c = Variable -> c -- | The initial context. initFreeEnv :: SingleVar c -> FreeEnv c type FreeM c = Reader (FreeEnv c) c -- | Base case: a variable. variable :: (Monoid c) => Int -> FreeM c -- | Going under a binder. bind :: FreeM a -> FreeM a -- | Changing the FlexRig context. go :: FlexRig -> FreeM a -> FreeM a -- | Changing the Relevance. goRel :: Relevance -> FreeM a -> FreeM a -- | What happens to the variables occurring under a constructor? underConstructor :: ConHead -> FreeM a -> FreeM a -- | Gather free variables in a collection. class Free' a c freeVars' :: (Free' a c, Monoid c) => a -> FreeM c instance GHC.Show.Show Agda.TypeChecking.Free.Lazy.IgnoreSorts instance GHC.Classes.Eq Agda.TypeChecking.Free.Lazy.IgnoreSorts instance GHC.Show.Show Agda.TypeChecking.Free.Lazy.VarOcc instance GHC.Classes.Eq Agda.TypeChecking.Free.Lazy.VarOcc instance GHC.Enum.Bounded Agda.TypeChecking.Free.Lazy.FlexRig instance GHC.Enum.Enum Agda.TypeChecking.Free.Lazy.FlexRig instance GHC.Show.Show Agda.TypeChecking.Free.Lazy.FlexRig instance GHC.Classes.Ord Agda.TypeChecking.Free.Lazy.FlexRig instance GHC.Classes.Eq Agda.TypeChecking.Free.Lazy.FlexRig instance GHC.Base.Monoid c => GHC.Base.Monoid (Agda.TypeChecking.Free.Lazy.FreeM c) instance Agda.TypeChecking.Free.Lazy.Free' Agda.Syntax.Internal.Term c instance Agda.TypeChecking.Free.Lazy.Free' Agda.Syntax.Internal.Type c instance Agda.TypeChecking.Free.Lazy.Free' Agda.Syntax.Internal.Sort c instance Agda.TypeChecking.Free.Lazy.Free' Agda.Syntax.Internal.Level c instance Agda.TypeChecking.Free.Lazy.Free' Agda.Syntax.Internal.PlusLevel c instance Agda.TypeChecking.Free.Lazy.Free' Agda.Syntax.Internal.LevelAtom c instance Agda.TypeChecking.Free.Lazy.Free' a c => Agda.TypeChecking.Free.Lazy.Free' [a] c instance Agda.TypeChecking.Free.Lazy.Free' a c => Agda.TypeChecking.Free.Lazy.Free' (GHC.Base.Maybe a) c instance (Agda.TypeChecking.Free.Lazy.Free' a c, Agda.TypeChecking.Free.Lazy.Free' b c) => Agda.TypeChecking.Free.Lazy.Free' (a, b) c instance Agda.TypeChecking.Free.Lazy.Free' a c => Agda.TypeChecking.Free.Lazy.Free' (Agda.Syntax.Internal.Elim' a) c instance Agda.TypeChecking.Free.Lazy.Free' a c => Agda.TypeChecking.Free.Lazy.Free' (Agda.Syntax.Internal.Arg a) c instance Agda.TypeChecking.Free.Lazy.Free' a c => Agda.TypeChecking.Free.Lazy.Free' (Agda.Syntax.Internal.Dom a) c instance Agda.TypeChecking.Free.Lazy.Free' a c => Agda.TypeChecking.Free.Lazy.Free' (Agda.Syntax.Internal.Abs a) c instance Agda.TypeChecking.Free.Lazy.Free' a c => Agda.TypeChecking.Free.Lazy.Free' (Agda.Syntax.Internal.Tele a) c instance Agda.TypeChecking.Free.Lazy.Free' Agda.Syntax.Internal.ClauseBody c instance Agda.TypeChecking.Free.Lazy.Free' Agda.Syntax.Internal.Clause c instance Test.QuickCheck.Arbitrary.Arbitrary Agda.TypeChecking.Free.Lazy.FlexRig instance Test.QuickCheck.Arbitrary.Arbitrary Agda.TypeChecking.Free.Lazy.VarOcc -- | Computing the free variables of a term. -- -- The distinction between rigid and strongly rigid occurrences comes -- from: Jason C. Reed, PhD thesis, 2009, page 96 (see also his LFMTP -- 2009 paper) -- -- The main idea is that x = t(x) is unsolvable if x occurs strongly -- rigidly in t. It might have a solution if the occurrence is not -- strongly rigid, e.g. -- -- x = f -> suc (f (x ( y -> k))) has x = f -> suc (f (suc k)) -- -- -- -- Under coinductive constructors, occurrences are never strongly rigid. -- Also, function types and lambdas do not establish strong rigidity. -- Only inductive constructors do so. (See issue 1271). module Agda.TypeChecking.Free -- | Free variables of a term, (disjointly) partitioned into strongly and -- and weakly rigid variables, flexible variables and irrelevant -- variables. data FreeVars FV :: VarSet -> VarSet -> VarSet -> VarSet -> VarSet -> VarSet -> FreeVars -- | Variables under only and at least one inductive constructor(s). [stronglyRigidVars] :: FreeVars -> VarSet -- | Variables at top or only under inductive record constructors λs and -- Πs. The purpose of recording these separately is that they can still -- become strongly rigid if put under a constructor whereas weakly rigid -- ones stay weakly rigid. [unguardedVars] :: FreeVars -> VarSet -- | Ordinary rigid variables, e.g., in arguments of variables. [weaklyRigidVars] :: FreeVars -> VarSet -- | Variables occuring in arguments of metas. These are only potentially -- free, depending how the meta variable is instantiated. [flexibleVars] :: FreeVars -> VarSet -- | Variables in irrelevant arguments and under a DontCare, i.e., -- in irrelevant positions. [irrelevantVars] :: FreeVars -> VarSet -- | Variables in UnusedArguments. [unusedVars] :: FreeVars -> VarSet type Free a = Free' a Any type FreeV a = Free' a FreeVars type FreeVS a = Free' a VarSet -- | Where should we skip sorts in free variable analysis? data IgnoreSorts -- | Do not skip. IgnoreNot :: IgnoreSorts -- | Skip when annotation to a type. IgnoreInAnnotations :: IgnoreSorts -- | Skip unconditionally. IgnoreAll :: IgnoreSorts -- | Collect all free variables. allFreeVars :: Free' a VarSet => a -> VarSet -- | Collect all relevant free variables. allRelevantVars :: Free' a VarSet => a -> VarSet -- | Collect all relevant free variables, possibly ignoring sorts. allRelevantVarsIgnoring :: Free' a VarSet => IgnoreSorts -> a -> VarSet freeIn :: Free a => Nat -> a -> Bool freeInIgnoringSorts :: Free a => Nat -> a -> Bool -- | Is the variable bound by the abstraction actually used? isBinderUsed :: Free a => Abs a -> Bool relevantIn :: Free a => Nat -> a -> Bool relevantInIgnoringSortAnn :: Free a => Nat -> a -> Bool data Occurrence NoOccurrence :: Occurrence Irrelevantly :: Occurrence -- | Under at least one and only inductive constructors. StronglyRigid :: Occurrence -- | In top position, or only under inductive record constructors. Unguarded :: Occurrence -- | In arguments to variables and definitions. WeaklyRigid :: Occurrence -- | In arguments of metas. Flexible :: Occurrence Unused :: Occurrence -- | Compute an occurrence of a single variable in a piece of internal -- syntax. occurrence :: FreeV a => Nat -> a -> Occurrence -- | Is the term entirely closed (no free variables)? closed :: Free' a All => a -> Bool -- | Doesn't go inside solved metas, but collects the variables from a -- metavariable application X ts as flexibleVars. freeVars :: (Monoid c, Singleton Variable c, Free' a c) => a -> c instance GHC.Show.Show Agda.TypeChecking.Free.Occurrence instance GHC.Classes.Eq Agda.TypeChecking.Free.Occurrence instance GHC.Show.Show Agda.TypeChecking.Free.FreeVars instance GHC.Classes.Eq Agda.TypeChecking.Free.FreeVars instance GHC.Base.Monoid Agda.TypeChecking.Free.FreeVars instance Agda.Utils.Singleton.Singleton Agda.TypeChecking.Free.Lazy.Variable Agda.TypeChecking.Free.FreeVars -- | Computing the free variables of a term. -- -- This is the old version of 'Free', using IntSets for -- the separate variable categories. We keep it as a specification. -- -- The distinction between rigid and strongly rigid occurrences comes -- from: Jason C. Reed, PhD thesis, 2009, page 96 (see also his LFMTP -- 2009 paper) -- -- The main idea is that x = t(x) is unsolvable if x occurs strongly -- rigidly in t. It might have a solution if the occurrence is not -- strongly rigid, e.g. -- -- x = f -> suc (f (x ( y -> k))) has x = f -> suc (f (suc k)) -- -- -- -- Under coinductive constructors, occurrences are never strongly rigid. -- Also, function types and lambdas do not establish strong rigidity. -- Only inductive constructors do so. (See issue 1271). module Agda.TypeChecking.Free.Old -- | Free variables of a term, (disjointly) partitioned into strongly and -- and weakly rigid variables, flexible variables and irrelevant -- variables. data FreeVars FV :: VarSet -> VarSet -> VarSet -> VarSet -> VarSet -> VarSet -> FreeVars -- | Variables under only and at least one inductive constructor(s). [stronglyRigidVars] :: FreeVars -> VarSet -- | Variables at top or only under inductive record constructors λs and -- Πs. The purpose of recording these separately is that they can still -- become strongly rigid if put under a constructor whereas weakly rigid -- ones stay weakly rigid. [unguardedVars] :: FreeVars -> VarSet -- | Ordinary rigid variables, e.g., in arguments of variables. [weaklyRigidVars] :: FreeVars -> VarSet -- | Variables occuring in arguments of metas. These are only potentially -- free, depending how the meta variable is instantiated. [flexibleVars] :: FreeVars -> VarSet -- | Variables in irrelevant arguments and under a DontCare, i.e., -- in irrelevant positions. [irrelevantVars] :: FreeVars -> VarSet -- | Variables in UnusedArguments. [unusedVars] :: FreeVars -> VarSet class Free a -- | Where should we skip sorts in free variable analysis? data IgnoreSorts -- | Do not skip. IgnoreNot :: IgnoreSorts -- | Skip when annotation to a type. IgnoreInAnnotations :: IgnoreSorts -- | Skip unconditionally. IgnoreAll :: IgnoreSorts -- | Doesn't go inside solved metas, but collects the variables from a -- metavariable application X ts as flexibleVars. freeVars :: Free a => a -> FreeVars freeVarsIgnore :: Free a => IgnoreSorts -> a -> FreeVars -- | allVars fv includes irrelevant variables. allVars :: FreeVars -> VarSet -- | All but the irrelevant variables. relevantVars :: FreeVars -> VarSet -- | Rigid variables: either strongly rigid, unguarded, or weakly rigid. rigidVars :: FreeVars -> VarSet freeIn :: Free a => Nat -> a -> Bool -- | Is the variable bound by the abstraction actually used? isBinderUsed :: Free a => Abs a -> Bool freeInIgnoringSorts :: Free a => Nat -> a -> Bool freeInIgnoringSortAnn :: Free a => Nat -> a -> Bool relevantIn :: Free a => Nat -> a -> Bool relevantInIgnoringSortAnn :: Free a => Nat -> a -> Bool data Occurrence NoOccurrence :: Occurrence Irrelevantly :: Occurrence -- | Under at least one and only inductive constructors. StronglyRigid :: Occurrence -- | In top position, or only under inductive record constructors. Unguarded :: Occurrence -- | In arguments to variables and definitions. WeaklyRigid :: Occurrence -- | In arguments of metas. Flexible :: Occurrence Unused :: Occurrence occurrence :: Nat -> FreeVars -> Occurrence instance GHC.Show.Show Agda.TypeChecking.Free.Old.IgnoreSorts instance GHC.Classes.Eq Agda.TypeChecking.Free.Old.IgnoreSorts instance GHC.Show.Show Agda.TypeChecking.Free.Old.Occurrence instance GHC.Classes.Eq Agda.TypeChecking.Free.Old.Occurrence instance GHC.Show.Show Agda.TypeChecking.Free.Old.FreeVars instance GHC.Classes.Eq Agda.TypeChecking.Free.Old.FreeVars instance GHC.Base.Monoid Agda.TypeChecking.Free.Old.FreeVars instance GHC.Base.Monoid Agda.TypeChecking.Free.Old.FreeT instance Agda.TypeChecking.Free.Old.Free Agda.Syntax.Internal.Term instance Agda.TypeChecking.Free.Old.Free Agda.Syntax.Internal.Type instance Agda.TypeChecking.Free.Old.Free Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Free.Old.Free Agda.Syntax.Internal.Level instance Agda.TypeChecking.Free.Old.Free Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Free.Old.Free Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.Free.Old.Free a => Agda.TypeChecking.Free.Old.Free [a] instance Agda.TypeChecking.Free.Old.Free a => Agda.TypeChecking.Free.Old.Free (GHC.Base.Maybe a) instance (Agda.TypeChecking.Free.Old.Free a, Agda.TypeChecking.Free.Old.Free b) => Agda.TypeChecking.Free.Old.Free (a, b) instance Agda.TypeChecking.Free.Old.Free a => Agda.TypeChecking.Free.Old.Free (Agda.Syntax.Internal.Elim' a) instance Agda.TypeChecking.Free.Old.Free a => Agda.TypeChecking.Free.Old.Free (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.Free.Old.Free a => Agda.TypeChecking.Free.Old.Free (Agda.Syntax.Internal.Dom a) instance Agda.TypeChecking.Free.Old.Free a => Agda.TypeChecking.Free.Old.Free (Agda.Syntax.Internal.Abs a) instance Agda.TypeChecking.Free.Old.Free a => Agda.TypeChecking.Free.Old.Free (Agda.Syntax.Internal.Tele a) instance Agda.TypeChecking.Free.Old.Free Agda.Syntax.Internal.ClauseBody instance Agda.TypeChecking.Free.Old.Free Agda.Syntax.Internal.Clause module Agda.Syntax.Internal.Pattern -- | Translate the clause patterns to terms with free variables bound by -- the clause telescope. -- -- Precondition: no projection patterns. clauseArgs :: Clause -> Args -- | Translate the clause patterns to an elimination spine with free -- variables bound by the clause telescope. clauseElims :: Clause -> Elims -- | Arity of a function, computed from clauses. class FunArity a funArity :: FunArity a => a -> Int -- | Get the number of initial Apply patterns. -- | Get the number of initial Apply patterns in a clause. -- | Get the number of common initial Apply patterns in a list of -- clauses. -- | Label the pattern variables from left to right using one label for -- each variable pattern and one for each dot pattern. class LabelPatVars a b i | b -> i -- | Intended, but unpractical due to the absence of type-level lambda, is: -- labelPatVars :: f (Pattern' x) -> State [i] (f (Pattern' -- (i,x))) labelPatVars :: LabelPatVars a b i => a -> State [i] b -- | Augment pattern variables with their de Bruijn index. numberPatVars :: LabelPatVars a b Int => Permutation -> a -> b patternsToElims :: Permutation -> [NamedArg Pattern] -> [Elim] -- | A OneholePattern is a linear pattern context P such -- that for any non-projection pattern p, inserting p -- into the single hole P[p], yields again a non-projection -- pattern. data OneHolePatterns OHPats :: [NamedArg Pattern] -> (NamedArg OneHolePattern) -> [NamedArg Pattern] -> OneHolePatterns data OneHolePattern Hole :: OneHolePattern -- | The type in ConPatternInfo serves the same role as in -- ConP. -- -- TODO: If a hole is plugged this type may have to be updated in some -- way. OHCon :: ConHead -> ConPatternInfo -> OneHolePatterns -> OneHolePattern plugHole :: Pattern -> OneHolePatterns -> [NamedArg Pattern] -- | allHoles ps returns for each pattern variable x in -- ps a context P such P[x] is one of the -- patterns of ps. The Ps are returned in the -- left-to-right order of the pattern variables in ps. allHoles :: [NamedArg Pattern] -> [OneHolePatterns] allHolesWithContents :: [NamedArg Pattern] -> [(Pattern, OneHolePatterns)] instance GHC.Show.Show Agda.Syntax.Internal.Pattern.OneHolePatterns instance GHC.Show.Show Agda.Syntax.Internal.Pattern.OneHolePattern instance Agda.Syntax.Abstract.IsProjP p => Agda.Syntax.Internal.Pattern.FunArity [p] instance Agda.Syntax.Internal.Pattern.FunArity Agda.Syntax.Internal.Clause instance Agda.Syntax.Internal.Pattern.FunArity [Agda.Syntax.Internal.Clause] instance Agda.Syntax.Internal.Pattern.LabelPatVars a b i => Agda.Syntax.Internal.Pattern.LabelPatVars (Agda.Syntax.Common.Arg c a) (Agda.Syntax.Common.Arg c b) i instance Agda.Syntax.Internal.Pattern.LabelPatVars a b i => Agda.Syntax.Internal.Pattern.LabelPatVars (Agda.Syntax.Common.Named x a) (Agda.Syntax.Common.Named x b) i instance Agda.Syntax.Internal.Pattern.LabelPatVars a b i => Agda.Syntax.Internal.Pattern.LabelPatVars [a] [b] i instance Agda.Syntax.Internal.Pattern.LabelPatVars (Agda.Syntax.Internal.Pattern' x) (Agda.Syntax.Internal.Pattern' (i, x)) i module Agda.TypeChecking.Monad.Base data TCState TCSt :: !PreScopeState -> !PostScopeState -> !PersistentTCState -> TCState -- | The state which is frozen after scope checking. [stPreScopeState] :: TCState -> !PreScopeState -- | The state which is modified after scope checking. [stPostScopeState] :: TCState -> !PostScopeState -- | State which is forever, like a diamond. [stPersistentState] :: TCState -> !PersistentTCState data PreScopeState PreScopeState :: CompressedFile -> InteractionPoints -> Signature -> Set ModuleName -> ModuleToSource -> VisitedModules -> ScopeInfo -> PatternSynDefns -> PatternSynDefns -> PragmaOptions -> BuiltinThings PrimFun -> Set String -> InteractionId -> NameId -> PreScopeState -- | Highlighting info for tokens (but not those tokens for which -- highlighting exists in stSyntaxInfo). [stPreTokens] :: PreScopeState -> CompressedFile [stPreInteractionPoints] :: PreScopeState -> InteractionPoints -- | Imported declared identifiers. Those most not be serialized! [stPreImports] :: PreScopeState -> Signature [stPreImportedModules] :: PreScopeState -> Set ModuleName [stPreModuleToSource] :: PreScopeState -> ModuleToSource [stPreVisitedModules] :: PreScopeState -> VisitedModules [stPreScope] :: PreScopeState -> ScopeInfo -- | Pattern synonyms of the current file. Serialized. [stPrePatternSyns] :: PreScopeState -> PatternSynDefns -- | Imported pattern synonyms. Must not be serialized! [stPrePatternSynImports] :: PreScopeState -> PatternSynDefns -- | Options applying to the current file. OPTIONS pragmas only -- affect this field. [stPrePragmaOptions] :: PreScopeState -> PragmaOptions [stPreImportedBuiltins] :: PreScopeState -> BuiltinThings PrimFun -- | Imports that should be generated by the compiler (this includes -- imports from imported modules). [stPreHaskellImports] :: PreScopeState -> Set String [stPreFreshInteractionId] :: PreScopeState -> InteractionId [stPreFreshNameId] :: PreScopeState -> NameId type DisambiguatedNames = IntMap QName data PostScopeState PostScopeState :: CompressedFile -> !DisambiguatedNames -> MetaStore -> InteractionPoints -> Constraints -> Constraints -> Bool -> Set QName -> Signature -> Maybe ModuleName -> TempInstanceTable -> Statistics -> Map MutualId (Set QName) -> BuiltinThings PrimFun -> MetaId -> MutualId -> CtxId -> ProblemId -> Int -> PostScopeState -- | Highlighting info. [stPostSyntaxInfo] :: PostScopeState -> CompressedFile -- | Disambiguation carried out by the type checker. Maps position of first -- name character to disambiguated QName for each -- AmbiguousQName already passed by the type checker. [stPostDisambiguatedNames] :: PostScopeState -> !DisambiguatedNames [stPostMetaStore] :: PostScopeState -> MetaStore [stPostInteractionPoints] :: PostScopeState -> InteractionPoints [stPostAwakeConstraints] :: PostScopeState -> Constraints [stPostSleepingConstraints] :: PostScopeState -> Constraints -- | Dirty when a constraint is added, used to prevent pointer update. -- Currently unused. [stPostDirty] :: PostScopeState -> Bool -- | Definitions to be considered during occurs check. Initialized to the -- current mutual block before the check. During occurs check, we remove -- definitions from this set as soon we have checked them. [stPostOccursCheckDefs] :: PostScopeState -> Set QName -- | Declared identifiers of the current file. These will be serialized -- after successful type checking. [stPostSignature] :: PostScopeState -> Signature -- | The current module is available after it has been type checked. [stPostCurrentModule] :: PostScopeState -> Maybe ModuleName [stPostInstanceDefs] :: PostScopeState -> TempInstanceTable -- | Counters to collect various statistics about meta variables etc. Only -- for current file. [stPostStatistics] :: PostScopeState -> Statistics [stPostMutualBlocks] :: PostScopeState -> Map MutualId (Set QName) [stPostLocalBuiltins] :: PostScopeState -> BuiltinThings PrimFun [stPostFreshMetaId] :: PostScopeState -> MetaId [stPostFreshMutualId] :: PostScopeState -> MutualId [stPostFreshCtxId] :: PostScopeState -> CtxId [stPostFreshProblemId] :: PostScopeState -> ProblemId [stPostFreshInt] :: PostScopeState -> Int -- | A part of the state which is not reverted when an error is thrown or -- the state is reset. data PersistentTCState PersistentTCSt :: DecodedModules -> CommandLineOptions -> InteractionOutputCallback -> !Benchmark -> !Statistics -> PersistentTCState [stDecodedModules] :: PersistentTCState -> DecodedModules [stPersistentOptions] :: PersistentTCState -> CommandLineOptions -- | Callback function to call when there is a response to give to the -- interactive frontend. See the documentation of -- InteractionOutputCallback. [stInteractionOutputCallback] :: PersistentTCState -> InteractionOutputCallback -- | Structure to track how much CPU time was spent on which Agda phase. -- Needs to be a strict field to avoid space leaks! [stBenchmark] :: PersistentTCState -> !Benchmark -- | Should be strict field. [stAccumStatistics] :: PersistentTCState -> !Statistics -- | Empty persistent state. initPersistentState :: PersistentTCState -- | Empty state of type checker. initPreScopeState :: PreScopeState initPostScopeState :: PostScopeState initState :: TCState stTokens :: Lens' CompressedFile TCState stImports :: Lens' Signature TCState stImportedModules :: Lens' (Set ModuleName) TCState stModuleToSource :: Lens' ModuleToSource TCState stVisitedModules :: Lens' VisitedModules TCState stScope :: Lens' ScopeInfo TCState stPatternSyns :: Lens' PatternSynDefns TCState stPatternSynImports :: Lens' PatternSynDefns TCState stPragmaOptions :: Lens' PragmaOptions TCState stImportedBuiltins :: Lens' (BuiltinThings PrimFun) TCState stHaskellImports :: Lens' (Set String) TCState stFreshInteractionId :: Lens' InteractionId TCState stFreshNameId :: Lens' NameId TCState stSyntaxInfo :: Lens' CompressedFile TCState stDisambiguatedNames :: Lens' DisambiguatedNames TCState stMetaStore :: Lens' MetaStore TCState stInteractionPoints :: Lens' InteractionPoints TCState stAwakeConstraints :: Lens' Constraints TCState stSleepingConstraints :: Lens' Constraints TCState stDirty :: Lens' Bool TCState stOccursCheckDefs :: Lens' (Set QName) TCState stSignature :: Lens' Signature TCState stCurrentModule :: Lens' (Maybe ModuleName) TCState stInstanceDefs :: Lens' TempInstanceTable TCState stStatistics :: Lens' Statistics TCState stMutualBlocks :: Lens' (Map MutualId (Set QName)) TCState stLocalBuiltins :: Lens' (BuiltinThings PrimFun) TCState stFreshMetaId :: Lens' MetaId TCState stFreshMutualId :: Lens' MutualId TCState stFreshCtxId :: Lens' CtxId TCState stFreshProblemId :: Lens' ProblemId TCState stFreshInt :: Lens' Int TCState stBuiltinThings :: TCState -> BuiltinThings PrimFun class Enum i => HasFresh i freshLens :: HasFresh i => Lens' i TCState nextFresh :: HasFresh i => TCState -> (i, TCState) fresh :: (HasFresh i, MonadState TCState m) => m i newtype ProblemId ProblemId :: Nat -> ProblemId freshName :: (MonadState TCState m, HasFresh NameId) => Range -> String -> m Name freshNoName :: (MonadState TCState m, HasFresh NameId) => Range -> m Name freshNoName_ :: (MonadState TCState m, HasFresh NameId) => m Name -- | Create a fresh name from a. class FreshName a freshName_ :: (FreshName a, MonadState TCState m, HasFresh NameId) => a -> m Name -- | Maps top-level module names to the corresponding source file names. type ModuleToSource = Map TopLevelModuleName AbsolutePath -- | Maps source file names to the corresponding top-level module names. type SourceToModule = Map AbsolutePath TopLevelModuleName -- | Creates a SourceToModule map based on stModuleToSource. sourceToModule :: TCM SourceToModule data ModuleInfo ModuleInfo :: Interface -> Bool -> ModuleInfo [miInterface] :: ModuleInfo -> Interface -- | True if warnings were encountered when the module was type -- checked. [miWarnings] :: ModuleInfo -> Bool type VisitedModules = Map TopLevelModuleName ModuleInfo type DecodedModules = Map TopLevelModuleName Interface data Interface Interface :: Hash -> [(ModuleName, Hash)] -> ModuleName -> Map ModuleName Scope -> ScopeInfo -> Signature -> BuiltinThings (String, QName) -> Set String -> HighlightingInfo -> [OptionsPragma] -> PatternSynDefns -> Interface -- | Hash of the source code. [iSourceHash] :: Interface -> Hash -- | Imported modules and their hashes. [iImportedModules] :: Interface -> [(ModuleName, Hash)] -- | Module name of this interface. [iModuleName] :: Interface -> ModuleName -- | Scope defined by this module. [iScope] :: Interface -> Map ModuleName Scope -- | Scope after we loaded this interface. Used in AtTopLevel and -- interactionLoop. -- -- Andreas, AIM XX: For performance reason, this field is not serialized, -- so if you deserialize an interface, iInsideScope will be -- empty. You need to type-check the file to get iInsideScope. [iInsideScope] :: Interface -> ScopeInfo [iSignature] :: Interface -> Signature [iBuiltin] :: Interface -> BuiltinThings (String, QName) -- | Haskell imports listed in (transitively) imported modules are not -- included here. [iHaskellImports] :: Interface -> Set String [iHighlighting] :: Interface -> HighlightingInfo -- | Pragma options set in the file. [iPragmaOptions] :: Interface -> [OptionsPragma] [iPatternSyns] :: Interface -> PatternSynDefns -- | Combines the source hash and the (full) hashes of the imported -- modules. iFullHash :: Interface -> Hash data Closure a Closure :: Signature -> TCEnv -> ScopeInfo -> a -> Closure a [clSignature] :: Closure a -> Signature [clEnv] :: Closure a -> TCEnv [clScope] :: Closure a -> ScopeInfo [clValue] :: Closure a -> a buildClosure :: a -> TCM (Closure a) type Constraints = [ProblemConstraint] data ProblemConstraint PConstr :: ProblemId -> Closure Constraint -> ProblemConstraint [constraintProblem] :: ProblemConstraint -> ProblemId [theConstraint] :: ProblemConstraint -> Closure Constraint data Constraint ValueCmp :: Comparison -> Type -> Term -> Term -> Constraint ElimCmp :: [Polarity] -> Type -> Term -> [Elim] -> [Elim] -> Constraint TypeCmp :: Comparison -> Type -> Type -> Constraint -- | the two types are for the error message only TelCmp :: Type -> Type -> Comparison -> Telescope -> Telescope -> Constraint SortCmp :: Comparison -> Sort -> Sort -> Constraint LevelCmp :: Comparison -> Level -> Level -> Constraint UnBlock :: MetaId -> Constraint Guarded :: Constraint -> ProblemId -> Constraint -- | The range is the one of the absurd pattern. IsEmpty :: Range -> Type -> Constraint -- | Check that the Type is either not a SIZELT or a non-empty -- SIZELT. CheckSizeLtSat :: Type -> Constraint FindInScope :: MetaId -> (Maybe [(Term, Type)]) -> Constraint data Comparison CmpEq :: Comparison CmpLeq :: Comparison -- | An extension of Comparison to >=. data CompareDirection DirEq :: CompareDirection DirLeq :: CompareDirection DirGeq :: CompareDirection -- | Embed Comparison into CompareDirection. fromCmp :: Comparison -> CompareDirection -- | Flip the direction of comparison. flipCmp :: CompareDirection -> CompareDirection -- | Turn a Comparison function into a CompareDirection -- function. -- -- Property: dirToCmp f (fromCmp cmp) = f cmp dirToCmp :: (Comparison -> a -> a -> c) -> CompareDirection -> a -> a -> c -- | A thing tagged with the context it came from. data Open a OpenThing :: [CtxId] -> a -> Open a [openThingCtxIds] :: Open a -> [CtxId] [openThing] :: Open a -> a -- | Parametrized since it is used without MetaId when creating a new meta. data Judgement a HasType :: a -> Type -> Judgement a [jMetaId] :: Judgement a -> a [jMetaType] :: Judgement a -> Type IsSort :: a -> Type -> Judgement a [jMetaId] :: Judgement a -> a [jMetaType] :: Judgement a -> Type data MetaVariable MetaVar :: MetaInfo -> MetaPriority -> Permutation -> Judgement MetaId -> MetaInstantiation -> Set Listener -> Frozen -> MetaVariable [mvInfo] :: MetaVariable -> MetaInfo -- | some metavariables are more eager to be instantiated [mvPriority] :: MetaVariable -> MetaPriority -- | a metavariable doesn't have to depend on all variables in the context, -- this "permutation" will throw away the ones it does not depend on [mvPermutation] :: MetaVariable -> Permutation [mvJudgement] :: MetaVariable -> Judgement MetaId [mvInstantiation] :: MetaVariable -> MetaInstantiation -- | meta variables scheduled for eta-expansion but blocked by this one [mvListeners] :: MetaVariable -> Set Listener -- | are we past the point where we can instantiate this meta variable? [mvFrozen] :: MetaVariable -> Frozen data Listener EtaExpand :: MetaId -> Listener CheckConstraint :: Nat -> ProblemConstraint -> Listener -- | Frozen meta variable cannot be instantiated by unification. This -- serves to prevent the completion of a definition by its use outside of -- the current block. (See issues 118, 288, 399). data Frozen -- | Do not instantiate. Frozen :: Frozen Instantiable :: Frozen data MetaInstantiation -- | solved by term (abstracted over some free variables) InstV :: [Arg String] -> Term -> MetaInstantiation -- | solved by Lam .. Sort s InstS :: Term -> MetaInstantiation -- | unsolved Open :: MetaInstantiation -- | open, to be instantiated as "implicit from scope" OpenIFS :: MetaInstantiation -- | solution blocked by unsolved constraints BlockedConst :: Term -> MetaInstantiation PostponedTypeCheckingProblem :: (Closure TypeCheckingProblem) -> (TCM Bool) -> MetaInstantiation data TypeCheckingProblem CheckExpr :: Expr -> Type -> TypeCheckingProblem CheckArgs :: ExpandHidden -> ExpandInstances -> Range -> [NamedArg Expr] -> Type -> Type -> (Args -> Type -> TCM Term) -> TypeCheckingProblem -- | (λ (xs : t₀) → e) : t This is not an instance of -- CheckExpr as the domain type has already been checked. For -- example, when checking (λ (x y : Fin _) → e) : (x : Fin n) → -- ? we want to postpone (λ (y : Fin n) → e) : ? where -- Fin n is a Type rather than an Expr. CheckLambda :: (Arg ([WithHiding Name], Maybe Type)) -> Expr -> Type -> TypeCheckingProblem -- | Meta variable priority: When we have an equation between -- meta-variables, which one should be instantiated? -- -- Higher value means higher priority to be instantiated. newtype MetaPriority MetaPriority :: Int -> MetaPriority data RunMetaOccursCheck RunMetaOccursCheck :: RunMetaOccursCheck DontRunMetaOccursCheck :: RunMetaOccursCheck -- | MetaInfo is cloned from one meta to the next during pruning. data MetaInfo MetaInfo :: Closure Range -> RunMetaOccursCheck -> MetaNameSuggestion -> MetaInfo [miClosRange] :: MetaInfo -> Closure Range -- | Run the extended occurs check that goes in definitions? [miMetaOccursCheck] :: MetaInfo -> RunMetaOccursCheck -- | Used for printing. Just x if meta-variable comes from omitted -- argument with name x. [miNameSuggestion] :: MetaInfo -> MetaNameSuggestion -- | Name suggestion for meta variable. Empty string means no suggestion. type MetaNameSuggestion = String -- | For printing, we couple a meta with its name suggestion. data NamedMeta NamedMeta :: MetaNameSuggestion -> MetaId -> NamedMeta [nmSuggestion] :: NamedMeta -> MetaNameSuggestion [nmid] :: NamedMeta -> MetaId type MetaStore = Map MetaId MetaVariable normalMetaPriority :: MetaPriority lowMetaPriority :: MetaPriority highMetaPriority :: MetaPriority getMetaInfo :: MetaVariable -> Closure Range getMetaScope :: MetaVariable -> ScopeInfo getMetaEnv :: MetaVariable -> TCEnv getMetaSig :: MetaVariable -> Signature getMetaRelevance :: MetaVariable -> Relevance getMetaColors :: MetaVariable -> [Color] -- | Interaction points are created by the scope checker who sets the -- range. The meta variable is created by the type checker and then -- hooked up to the interaction point. data InteractionPoint InteractionPoint :: Range -> Maybe MetaId -> InteractionPoint -- | The position of the interaction point. [ipRange] :: InteractionPoint -> Range -- | The meta variable, if any, holding the type etc. [ipMeta] :: InteractionPoint -> Maybe MetaId -- | Data structure managing the interaction points. type InteractionPoints = Map InteractionId InteractionPoint data Signature Sig :: Sections -> Definitions -> RewriteRuleMap -> Signature [_sigSections] :: Signature -> Sections [_sigDefinitions] :: Signature -> Definitions -- | The rewrite rules defined in this file. [_sigRewriteRules] :: Signature -> RewriteRuleMap sigSections :: Lens' Sections Signature sigDefinitions :: Lens' Definitions Signature sigRewriteRules :: Lens' RewriteRuleMap Signature type Sections = Map ModuleName Section type Definitions = HashMap QName Definition type RewriteRuleMap = HashMap QName RewriteRules data Section Section :: Telescope -> Section [_secTelescope] :: Section -> Telescope secTelescope :: Lens' Telescope Section emptySignature :: Signature -- | A DisplayForm is in essence a rewrite rule q ts --> -- dt for a defined symbol (could be a constructor as well) -- q. The right hand side is a DisplayTerm which is used -- to reify to a more readable Syntax. -- -- The patterns ts are just terms, but var 0 is -- interpreted as a hole. Each occurrence of var 0 is a new hole -- (pattern var). For each *occurrence* of var0 the rhs -- dt has a free variable. These are instantiated when matching -- a display form against a term q vs succeeds. data DisplayForm Display :: Nat -> [Term] -> DisplayTerm -> DisplayForm -- | Number n of free variables in dfRHS. [dfFreeVars] :: DisplayForm -> Nat -- | Left hand side patterns, where var 0 stands for a pattern -- variable. There should be n occurrences of var0 in -- dfPats. [dfPats] :: DisplayForm -> [Term] -- | Right hand side, with n free variables. [dfRHS] :: DisplayForm -> DisplayTerm -- | A structured presentation of a Term for reification into -- Syntax. data DisplayTerm -- | (f vs | ws) us. The first DisplayTerm is the parent -- function f with its args vs. The list of -- DisplayTerms are the with expressions ws. The -- Args are additional arguments us (possible in case the -- with-application is of function type). DWithApp :: DisplayTerm -> [DisplayTerm] -> Args -> DisplayTerm -- | c vs. DCon :: ConHead -> [Arg DisplayTerm] -> DisplayTerm -- | d vs. DDef :: QName -> [Elim' DisplayTerm] -> DisplayTerm -- | .v. DDot :: Term -> DisplayTerm -- | v. DTerm :: Term -> DisplayTerm -- | By default, we have no display form. defaultDisplayForm :: QName -> [Open DisplayForm] defRelevance :: Definition -> Relevance defColors :: Definition -> [Color] -- | Non-linear (non-constructor) first-order pattern. data NLPat -- | Matches anything (modulo non-linearity). PVar :: {-# UNPACK #-} !Int -> NLPat -- | Matches anything (e.g. irrelevant terms). PWild :: NLPat -- | Matches f es PDef :: QName -> PElims -> NLPat -- | Matches λ x → t PLam :: ArgInfo -> (Abs NLPat) -> NLPat -- | Matches (x : A) → B PPi :: (Dom (Type' NLPat)) -> (Abs (Type' NLPat)) -> NLPat -- | Matches x es where x is a lambda-bound variable PBoundVar :: {-# UNPACK #-} !Int -> PElims -> NLPat -- | Matches the term modulo β (ideally βη). PTerm :: Term -> NLPat type PElims = [Elim' NLPat] type RewriteRules = [RewriteRule] -- | Rewrite rules can be added independently from function clauses. data RewriteRule RewriteRule :: QName -> Telescope -> NLPat -> Term -> Type -> RewriteRule -- | Name of rewrite rule q : Γ → lhs ≡ rhs where is -- the rewrite relation. [rewName] :: RewriteRule -> QName -- | Γ. [rewContext] :: RewriteRule -> Telescope -- | Γ ⊢ lhs : t. [rewLHS] :: RewriteRule -> NLPat -- | Γ ⊢ rhs : t. [rewRHS] :: RewriteRule -> Term -- | Γ ⊢ t. [rewType] :: RewriteRule -> Type data Definition Defn :: ArgInfo -> QName -> Type -> [Polarity] -> [Occurrence] -> [Open DisplayForm] -> MutualId -> CompiledRepresentation -> Maybe QName -> Defn -> Definition -- | Hiding should not be used. [defArgInfo] :: Definition -> ArgInfo [defName] :: Definition -> QName -- | Type of the lifted definition. [defType] :: Definition -> Type -- | Variance information on arguments of the definition. Does not include -- info for dropped parameters to projection(-like) functions and -- constructors. [defPolarity] :: Definition -> [Polarity] -- | Positivity information on arguments of the definition. Does not -- include info for dropped parameters to projection(-like) functions and -- constructors. [defArgOccurrences] :: Definition -> [Occurrence] [defDisplay] :: Definition -> [Open DisplayForm] [defMutual] :: Definition -> MutualId [defCompiledRep] :: Definition -> CompiledRepresentation -- | Just q when this definition is an instance of class q [defInstance] :: Definition -> Maybe QName [theDef] :: Definition -> Defn -- | Create a definition with sensible defaults. defaultDefn :: ArgInfo -> QName -> Type -> Defn -> Definition type HaskellCode = String type HaskellType = String type EpicCode = String type JSCode = Exp data HaskellRepresentation HsDefn :: HaskellType -> HaskellCode -> HaskellRepresentation HsType :: HaskellType -> HaskellRepresentation data HaskellExport HsExport :: HaskellType -> String -> HaskellExport -- | Polarity for equality and subtype checking. data Polarity -- | monotone Covariant :: Polarity -- | antitone Contravariant :: Polarity -- | no information (mixed variance) Invariant :: Polarity -- | constant Nonvariant :: Polarity data CompiledRepresentation CompiledRep :: Maybe HaskellRepresentation -> Maybe HaskellExport -> Maybe EpicCode -> Maybe JSCode -> CompiledRepresentation [compiledHaskell] :: CompiledRepresentation -> Maybe HaskellRepresentation [exportHaskell] :: CompiledRepresentation -> Maybe HaskellExport [compiledEpic] :: CompiledRepresentation -> Maybe EpicCode [compiledJS] :: CompiledRepresentation -> Maybe JSCode noCompiledRep :: CompiledRepresentation -- | Additional information for extended lambdas. data ExtLamInfo ExtLamInfo :: Int -> Int -> ExtLamInfo [extLamNumHidden] :: ExtLamInfo -> Int [extLamNumNonHid] :: ExtLamInfo -> Int -- | Additional information for projection Functions. data Projection Projection :: Maybe QName -> QName -> Int -> Term -> ArgInfo -> Projection -- | Nothing if only projection-like, Just q if record -- projection, where q is the original projection name (current -- name could be from module app). [projProper] :: Projection -> Maybe QName -- | Type projected from. Record type if projProper = Just{}. [projFromType] :: Projection -> QName -- | Index of the record argument. Start counting with 1, because 0 means -- that it is already applied to the record value. This can happen in -- module instantiation, but then either the record value is var -- 0, or funProjection == Nothing. [projIndex] :: Projection -> Int -- | Term t to be be applied to record parameters and record -- value. The parameters will be dropped. In case of a proper projection, -- a postfix projection application will be created: t = pars r -> -- r .p (Invariant: the number of abstractions equals -- projIndex.) In case of a projection-like function, just the -- function symbol is returned as Def: t = pars -> f. [projDropPars] :: Projection -> Term -- | The info of the principal (record) argument. [projArgInfo] :: Projection -> ArgInfo data Defn -- | Postulate. Axiom :: Defn Function :: [Clause] -> Maybe CompiledClauses -> FunctionInverse -> [QName] -> IsAbstract -> Delayed -> Maybe Projection -> Bool -> Bool -> Maybe Bool -> Maybe ExtLamInfo -> Maybe QName -> Bool -> Defn [funClauses] :: Defn -> [Clause] -- | Nothing while function is still type-checked. Just cc -- after type and coverage checking and translation to case trees. [funCompiled] :: Defn -> Maybe CompiledClauses [funInv] :: Defn -> FunctionInverse -- | Mutually recursive functions, datas and records. -- Does not include this function. [funMutual] :: Defn -> [QName] [funAbstr] :: Defn -> IsAbstract -- | Are the clauses of this definition delayed? [funDelayed] :: Defn -> Delayed -- | Is it a record projection? If yes, then return the name of the record -- type and index of the record argument. Start counting with 1, because -- 0 means that it is already applied to the record. (Can happen in -- module instantiation.) This information is used in the termination -- checker. [funProjection] :: Defn -> Maybe Projection -- | Should calls to this function be normalised at compile-time? [funStatic] :: Defn -> Bool -- | Has this function been created by a module instantiation? [funCopy] :: Defn -> Bool -- | Has this function been termination checked? Did it pass? [funTerminates] :: Defn -> Maybe Bool -- | Is this function generated from an extended lambda? If yes, then -- return the number of hidden and non-hidden lambda-lifted arguments [funExtLam] :: Defn -> Maybe ExtLamInfo -- | Is this a generated with-function? If yes, then what's the name of the -- parent function. [funWith] :: Defn -> Maybe QName -- | Is this a function defined by copatterns? [funCopatternLHS] :: Defn -> Bool Datatype :: Nat -> Permutation -> Drop Permutation -> Nat -> Induction -> (Maybe Clause) -> [QName] -> Sort -> [QName] -> IsAbstract -> Defn -- | Number of parameters. [dataPars] :: Defn -> Nat -- | Parameters that are maybe small. [dataSmallPars] :: Defn -> Permutation -- | Parameters that appear in indices. [dataNonLinPars] :: Defn -> Drop Permutation -- | Number of indices. [dataIxs] :: Defn -> Nat -- | data or codata (legacy). [dataInduction] :: Defn -> Induction -- | This might be in an instantiated module. [dataClause] :: Defn -> (Maybe Clause) -- | Constructor names. [dataCons] :: Defn -> [QName] [dataSort] :: Defn -> Sort -- | Mutually recursive functions, datas and records. -- Does not include this data type. [dataMutual] :: Defn -> [QName] [dataAbstr] :: Defn -> IsAbstract Record :: Nat -> Maybe Clause -> ConHead -> Bool -> Type -> [Arg QName] -> Telescope -> [QName] -> Bool -> Maybe Induction -> Bool -> IsAbstract -> Defn -- | Number of parameters. [recPars] :: Defn -> Nat [recClause] :: Defn -> Maybe Clause -- | Constructor name and fields. [recConHead] :: Defn -> ConHead [recNamedCon] :: Defn -> Bool -- | The record constructor's type. (Includes record parameters.) [recConType] :: Defn -> Type [recFields] :: Defn -> [Arg QName] -- | The record field telescope. (Includes record parameters.) Note: -- TelV recTel _ == telView' recConType. Thus, recTel -- is redundant. [recTel] :: Defn -> Telescope -- | Mutually recursive functions, datas and records. -- Does not include this record. [recMutual] :: Defn -> [QName] -- | Eta-expand at this record type. False for unguarded recursive -- records and coinductive records. [recEtaEquality] :: Defn -> Bool -- | Inductive or CoInductive? Matters only for recursive -- records. Nothing means that the user did not specify it, which -- is an error for recursive records. [recInduction] :: Defn -> Maybe Induction -- | Recursive record. Implies recEtaEquality = False. Projections -- are not size-preserving. [recRecursive] :: Defn -> Bool [recAbstr] :: Defn -> IsAbstract Constructor :: Nat -> ConHead -> QName -> IsAbstract -> Induction -> Defn -- | Number of parameters. [conPars] :: Defn -> Nat -- | Name of (original) constructor and fields. (This might be in a module -- instance.) [conSrcCon] :: Defn -> ConHead -- | Name of datatype or record type. [conData] :: Defn -> QName [conAbstr] :: Defn -> IsAbstract -- | Inductive or coinductive? [conInd] :: Defn -> Induction -- | Primitive or builtin functions. Primitive :: IsAbstract -> String -> [Clause] -> Maybe CompiledClauses -> Defn [primAbstr] :: Defn -> IsAbstract [primName] :: Defn -> String -- | null for primitive functions, not null for builtin -- functions. [primClauses] :: Defn -> [Clause] -- | Nothing for primitive functions, Just something -- for builtin functions. [primCompiled] :: Defn -> Maybe CompiledClauses -- | A template for creating Function definitions, with sensible -- defaults. emptyFunction :: Defn -- | Checking whether we are dealing with a function yet to be defined. isEmptyFunction :: Defn -> Bool isCopatternLHS :: [Clause] -> Bool recCon :: Defn -> QName defIsRecord :: Defn -> Bool defIsDataOrRecord :: Defn -> Bool newtype Fields Fields :: [(Name, Type)] -> Fields -- | Did we encounter a simplifying reduction? In terms of CIC, that would -- be a iota-reduction. In terms of Agda, this is a constructor or -- literal pattern that matched. Just beta-reduction (substitution) or -- delta-reduction (unfolding of definitions) does not count as -- simplifying? data Simplification YesSimplification :: Simplification NoSimplification :: Simplification data Reduced no yes NoReduction :: no -> Reduced no yes YesReduction :: Simplification -> yes -> Reduced no yes -- | Three cases: 1. not reduced, 2. reduced, but blocked, 3. reduced, not -- blocked. data IsReduced NotReduced :: IsReduced Reduced :: (Blocked ()) -> IsReduced data MaybeReduced a MaybeRed :: IsReduced -> a -> MaybeReduced a [isReduced] :: MaybeReduced a -> IsReduced [ignoreReduced] :: MaybeReduced a -> a type MaybeReducedArgs = [MaybeReduced (Arg Term)] type MaybeReducedElims = [MaybeReduced Elim] notReduced :: a -> MaybeReduced a reduced :: Blocked (Arg Term) -> MaybeReduced (Arg Term) -- | Controlling reduce. data AllowedReduction -- | (Projection and) projection-like functions may be reduced. ProjectionReductions :: AllowedReduction -- | Functions which are not projections may be reduced. FunctionReductions :: AllowedReduction -- | Reduce Level terms. LevelReductions :: AllowedReduction -- | Functions that have not passed termination checking. NonTerminatingReductions :: AllowedReduction type AllowedReductions = [AllowedReduction] -- | Not quite all reductions (skip non-terminating reductions) allReductions :: AllowedReductions data PrimFun PrimFun :: QName -> Arity -> ([Arg Term] -> ReduceM (Reduced MaybeReducedArgs Term)) -> PrimFun [primFunName] :: PrimFun -> QName [primFunArity] :: PrimFun -> Arity [primFunImplementation] :: PrimFun -> [Arg Term] -> ReduceM (Reduced MaybeReducedArgs Term) defClauses :: Definition -> [Clause] defCompiled :: Definition -> Maybe CompiledClauses defJSDef :: Definition -> Maybe JSCode defEpicDef :: Definition -> Maybe EpicCode -- | Are the clauses of this definition delayed? defDelayed :: Definition -> Delayed -- | Has the definition failed the termination checker? defNonterminating :: Definition -> Bool -- | Is the definition just a copy created by a module instantiation? defCopy :: Definition -> Bool -- | Beware when using this function on a def obtained with -- getConstInfo q! If the identifier q is abstract, -- getConstInfo will turn its def into an Axiom -- and you always get ConcreteDef, paradoxically. Use it in -- IgnoreAbstractMode, like this: a ignoreAbstractMode $ -- defAbstract <$ getConstInfo q defAbstract :: Definition -> IsAbstract type FunctionInverse = FunctionInverse' Clause data FunctionInverse' c NotInjective :: FunctionInverse' c Inverse :: (Map TermHead c) -> FunctionInverse' c data TermHead SortHead :: TermHead PiHead :: TermHead ConsHead :: QName -> TermHead newtype MutualId MutId :: Int32 -> MutualId type Statistics = Map String Integer data Call CheckClause :: Type -> SpineClause -> Call CheckPattern :: Pattern -> Telescope -> Type -> Call CheckLetBinding :: LetBinding -> Call InferExpr :: Expr -> Call CheckExprCall :: Expr -> Type -> Call CheckDotPattern :: Expr -> Term -> Call CheckPatternShadowing :: SpineClause -> Call IsTypeCall :: Expr -> Sort -> Call IsType_ :: Expr -> Call InferVar :: Name -> Call InferDef :: Range -> QName -> Call CheckArguments :: Range -> [NamedArg Expr] -> Type -> Type -> Call CheckDataDef :: Range -> Name -> [LamBinding] -> [Constructor] -> Call CheckRecDef :: Range -> Name -> [LamBinding] -> [Constructor] -> Call CheckConstructor :: QName -> Telescope -> Sort -> Constructor -> Call CheckFunDef :: Range -> Name -> [Clause] -> Call CheckPragma :: Range -> Pragma -> Call CheckPrimitive :: Range -> Name -> Expr -> Call CheckIsEmpty :: Range -> Type -> Call CheckWithFunctionType :: Expr -> Call CheckSectionApplication :: Range -> ModuleName -> ModuleApplication -> Call ScopeCheckExpr :: Expr -> Call ScopeCheckDeclaration :: NiceDeclaration -> Call ScopeCheckLHS :: Name -> Pattern -> Call NoHighlighting :: Call -- | used by setCurrentRange SetRange :: Range -> Call -- | The instance table is a Map associating to every name of -- recorddata typepostulate its list of instances type InstanceTable = Map QName [QName] -- | When typechecking something of the following form: -- -- instance x : _ x = y -- -- it's not yet known where to add x, so we add it to a list of -- unresolved instances and we'll deal with it later. type TempInstanceTable = (InstanceTable, [QName]) data BuiltinDescriptor BuiltinData :: (TCM Type) -> [String] -> BuiltinDescriptor BuiltinDataCons :: (TCM Type) -> BuiltinDescriptor BuiltinPrim :: String -> (Term -> TCM ()) -> BuiltinDescriptor BuiltinPostulate :: Relevance -> (TCM Type) -> BuiltinDescriptor -- | Builtin of any kind. Type can be checked (Just t) or inferred -- (Nothing). The second argument is the hook for the -- verification function. BuiltinUnknown :: (Maybe (TCM Type)) -> (Term -> Type -> TCM ()) -> BuiltinDescriptor data BuiltinInfo BuiltinInfo :: String -> BuiltinDescriptor -> BuiltinInfo [builtinName] :: BuiltinInfo -> String [builtinDesc] :: BuiltinInfo -> BuiltinDescriptor type BuiltinThings pf = Map String (Builtin pf) data Builtin pf Builtin :: Term -> Builtin pf Prim :: pf -> Builtin pf -- | How much highlighting should be sent to the user interface? data HighlightingLevel None :: HighlightingLevel NonInteractive :: HighlightingLevel -- | This includes both non-interactive highlighting and interactive -- highlighting of the expression that is currently being type-checked. Interactive :: HighlightingLevel -- | How should highlighting be sent to the user interface? data HighlightingMethod -- | Via stdout. Direct :: HighlightingMethod -- | Both via files and via stdout. Indirect :: HighlightingMethod -- | ifTopLevelAndHighlightingLevelIs l m runs m when -- we're type-checking the top-level module and the highlighting level is -- at least l. ifTopLevelAndHighlightingLevelIs :: MonadTCM tcm => HighlightingLevel -> tcm () -> tcm () data TCEnv TCEnv :: Context -> LetBindings -> ModuleName -> Maybe AbsolutePath -> [(ModuleName, Nat)] -> [TopLevelModuleName] -> Maybe MutualId -> TerminationCheck () -> Bool -> Bool -> [ProblemId] -> AbstractMode -> Relevance -> [Color] -> Bool -> Bool -> Bool -> Range -> Range -> Maybe (Closure Call) -> HighlightingLevel -> HighlightingMethod -> Integer -> Bool -> ExpandHidden -> Maybe QName -> Simplification -> AllowedReductions -> Bool -> Bool -> Bool -> Bool -> TCEnv [envContext] :: TCEnv -> Context [envLetBindings] :: TCEnv -> LetBindings [envCurrentModule] :: TCEnv -> ModuleName -- | The path to the file that is currently being type-checked. -- Nothing if we do not have a file (like in interactive mode see -- CommandLine). [envCurrentPath] :: TCEnv -> Maybe AbsolutePath -- | anonymous modules and their number of free variables [envAnonymousModules] :: TCEnv -> [(ModuleName, Nat)] -- | to detect import cycles [envImportPath] :: TCEnv -> [TopLevelModuleName] -- | the current (if any) mutual block [envMutualBlock] :: TCEnv -> Maybe MutualId -- | are we inside the scope of a termination pragma [envTerminationCheck] :: TCEnv -> TerminationCheck () -- | Are we currently in the process of solving active constraints? [envSolvingConstraints] :: TCEnv -> Bool -- | Are we allowed to assign metas? [envAssignMetas] :: TCEnv -> Bool [envActiveProblems] :: TCEnv -> [ProblemId] -- | When checking the typesignature of a public definition or the body of -- a non-abstract definition this is true. To prevent information about -- abstract things leaking outside the module. [envAbstractMode] :: TCEnv -> AbstractMode -- | Are we checking an irrelevant argument? (=Irrelevant) Then -- top-level irrelevant declarations are enabled. Other value: -- Relevant, then only relevant decls. are avail. [envRelevance] :: TCEnv -> Relevance [envColors] :: TCEnv -> [Color] -- | Sometimes we want to disable display forms. [envDisplayFormsEnabled] :: TCEnv -> Bool -- | should we try to recover interaction points when reifying? disabled -- when generating types for with functions [envReifyInteractionPoints] :: TCEnv -> Bool -- | it's safe to eta contract implicit lambdas as long as we're not going -- to reify and retypecheck (like when doing with abstraction) [envEtaContractImplicit] :: TCEnv -> Bool [envRange] :: TCEnv -> Range -- | Interactive highlighting uses this range rather than envRange. [envHighlightingRange] :: TCEnv -> Range -- | what we're doing at the moment [envCall] :: TCEnv -> Maybe (Closure Call) -- | Set to None when imported modules are type-checked. [envHighlightingLevel] :: TCEnv -> HighlightingLevel [envHighlightingMethod] :: TCEnv -> HighlightingMethod -- | This number indicates how far away from the top-level module Agda has -- come when chasing modules. The level of a given module is not -- necessarily the same as the length, in the module dependency graph, of -- the shortest path from the top-level module; it depends on in which -- order Agda chooses to chase dependencies. [envModuleNestingLevel] :: TCEnv -> Integer -- | When True, allows destructively shared updating terms during -- evaluation or unification. This is disabled when doing speculative -- checking, like solve instance metas, or when updating might break -- abstraction, as is the case when checking abstract definitions. [envAllowDestructiveUpdate] :: TCEnv -> Bool -- | When type-checking an alias f=e, we do not want to insert hidden -- arguments in the end, because these will become unsolved metas. [envExpandLast] :: TCEnv -> ExpandHidden -- | We are reducing an application of this function. (For debugging of -- incomplete matches only.) [envAppDef] :: TCEnv -> Maybe QName -- | Did we encounter a simplification (proper match) during the current -- reduction process? [envSimplification] :: TCEnv -> Simplification [envAllowedReductions] :: TCEnv -> AllowedReductions -- | Can we compare blocked things during conversion? No by default. Yes -- for rewriting feature. [envCompareBlocked] :: TCEnv -> Bool -- | When True types will be omitted from printed pi types if they can be -- inferred [envPrintDomainFreePi] :: TCEnv -> Bool -- | Used by the scope checker to make sure that certain forms of -- expressions are not used inside dot patterns: extended lambdas and -- let-expressions. [envInsideDotPattern] :: TCEnv -> Bool -- | The rules for translating internal to abstract syntax are slightly -- different when the internal term comes from an unquote. [envReifyUnquoted] :: TCEnv -> Bool initEnv :: TCEnv -- | The Context is a stack of ContextEntrys. type Context = [ContextEntry] data ContextEntry Ctx :: CtxId -> Dom (Name, Type) -> ContextEntry [ctxId] :: ContextEntry -> CtxId [ctxEntry] :: ContextEntry -> Dom (Name, Type) newtype CtxId CtxId :: Nat -> CtxId type LetBindings = Map Name (Open (Term, Dom Type)) data AbstractMode -- | Abstract things in the current module can be accessed. AbstractMode :: AbstractMode -- | No abstract things can be accessed. ConcreteMode :: AbstractMode -- | All abstract things can be accessed. IgnoreAbstractMode :: AbstractMode data ExpandHidden -- | Add implicit arguments in the end until type is no longer hidden -- Pi. ExpandLast :: ExpandHidden -- | Do not append implicit arguments. DontExpandLast :: ExpandHidden data ExpandInstances ExpandInstanceArguments :: ExpandInstances DontExpandInstanceArguments :: ExpandInstances data Occ OccCon :: QName -> QName -> OccPos -> Occ [occDatatype] :: Occ -> QName [occConstructor] :: Occ -> QName [occPosition] :: Occ -> OccPos OccClause :: QName -> Int -> OccPos -> Occ [occFunction] :: Occ -> QName [occClause] :: Occ -> Int [occPosition] :: Occ -> OccPos data OccPos NonPositively :: OccPos ArgumentTo :: Nat -> QName -> OccPos -- | Information about a call. data CallInfo CallInfo :: QName -> Range -> Closure Term -> CallInfo -- | Target function name. [callInfoTarget] :: CallInfo -> QName -- | Range of the target function. [callInfoRange] :: CallInfo -> Range -- | To be formatted representation of the call. [callInfoCall] :: CallInfo -> Closure Term -- | We only show the name of the callee. -- | Information about a mutual block which did not pass the termination -- checker. data TerminationError TerminationError :: [QName] -> [CallInfo] -> TerminationError -- | The functions which failed to check. (May not include automatically -- generated functions.) [termErrFunctions] :: TerminationError -> [QName] -- | The problematic call sites. [termErrCalls] :: TerminationError -> [CallInfo] -- | Error when splitting a pattern variable into possible constructor -- patterns. data SplitError -- | Neither data type nor record. NotADatatype :: (Closure Type) -> SplitError -- | Data type, but in irrelevant position. IrrelevantDatatype :: (Closure Type) -> SplitError -- | Split on codata not allowed. UNUSED, but keep! -- | -- NoRecordConstructor Type -- ^ record type, but no constructor CoinductiveDatatype :: (Closure Type) -> SplitError CantSplit :: QName -> Telescope -> Args -> Args -> SplitError -- | Constructor. [cantSplitConName] :: SplitError -> QName -- | Context for indices. [cantSplitTel] :: SplitError -> Telescope -- | Inferred indices (from type of constructor). [cantSplitConIdx] :: SplitError -> Args -- | Expected indices (from checking pattern). [cantSplitGivenIdx] :: SplitError -> Args GenericSplitError :: String -> SplitError data UnquoteError BadVisibility :: String -> (Arg Term) -> UnquoteError ConInsteadOfDef :: QName -> String -> String -> UnquoteError DefInsteadOfCon :: QName -> String -> String -> UnquoteError -- |
--   NotAConstructor kind term
--   
NotAConstructor :: String -> Term -> UnquoteError NotALiteral :: String -> Term -> UnquoteError RhsUsesDottedVar :: [Int] -> Term -> UnquoteError BlockedOnMeta :: MetaId -> UnquoteError UnquotePanic :: String -> UnquoteError data TypeError InternalError :: String -> TypeError NotImplemented :: String -> TypeError NotSupported :: String -> TypeError CompilationError :: String -> TypeError TerminationCheckFailed :: [TerminationError] -> TypeError PropMustBeSingleton :: TypeError DataMustEndInSort :: Term -> TypeError -- | The target of a constructor isn't an application of its datatype. The -- Type records what it does target. ShouldEndInApplicationOfTheDatatype :: Type -> TypeError -- | The target of a constructor isn't its datatype applied to something -- that isn't the parameters. First term is the correct target and the -- second term is the actual target. ShouldBeAppliedToTheDatatypeParameters :: Term -> Term -> TypeError -- | Expected a type to be an application of a particular datatype. ShouldBeApplicationOf :: Type -> QName -> TypeError -- | constructor, datatype ConstructorPatternInWrongDatatype :: QName -> QName -> TypeError -- | Indices. IndicesNotConstructorApplications :: [Arg Term] -> TypeError -- | Variables, indices. IndexVariablesNotDistinct :: [Nat] -> [Arg Term] -> TypeError -- | Indices (variables), index expressions (with constructors applied to -- reconstructed parameters), parameters. IndicesFreeInParameters :: [Nat] -> [Arg Term] -> [Arg Term] -> TypeError -- | Datatype, constructors. CantResolveOverloadedConstructorsTargetingSameDatatype :: QName -> [QName] -> TypeError -- | constructor, type DoesNotConstructAnElementOf :: QName -> Type -> TypeError -- | Varying number of arguments for a function. DifferentArities :: TypeError -- | The left hand side of a function definition has a hidden argument -- where a non-hidden was expected. WrongHidingInLHS :: TypeError -- | Expected a non-hidden function and found a hidden lambda. WrongHidingInLambda :: Type -> TypeError -- | A function is applied to a hidden argument where a non-hidden was -- expected. WrongHidingInApplication :: Type -> TypeError -- | A function is applied to a hidden named argument it does not have. WrongNamedArgument :: (NamedArg Expr) -> TypeError -- | Expected a relevant function and found an irrelevant lambda. WrongIrrelevanceInLambda :: Type -> TypeError -- | The given hiding does not correspond to the expected hiding. HidingMismatch :: Hiding -> Hiding -> TypeError -- | The given relevance does not correspond to the expected relevane. RelevanceMismatch :: Relevance -> Relevance -> TypeError -- | The given color does not correspond to the expected color. ColorMismatch :: [Color] -> [Color] -> TypeError -- | The term does not correspond to an inductive data type. NotInductive :: Term -> TypeError UninstantiatedDotPattern :: Expr -> TypeError IlltypedPattern :: Pattern -> Type -> TypeError IllformedProjectionPattern :: Pattern -> TypeError CannotEliminateWithPattern :: (NamedArg Pattern) -> Type -> TypeError TooManyArgumentsInLHS :: Type -> TypeError WrongNumberOfConstructorArguments :: QName -> Nat -> Nat -> TypeError ShouldBeEmpty :: Type -> [Pattern] -> TypeError -- | The given type should have been a sort. ShouldBeASort :: Type -> TypeError -- | The given type should have been a pi. ShouldBePi :: Type -> TypeError ShouldBeRecordType :: Type -> TypeError ShouldBeRecordPattern :: Pattern -> TypeError NotAProjectionPattern :: (NamedArg Pattern) -> TypeError NotAProperTerm :: TypeError SetOmegaNotValidType :: TypeError -- | This sort is not a type expression. InvalidTypeSort :: Sort -> TypeError -- | This term is not a type expression. InvalidType :: Term -> TypeError -- | This term, a function type constructor, lives in SizeUniv, -- which is not allowed. FunctionTypeInSizeUniv :: Term -> TypeError SplitOnIrrelevant :: Pattern -> (Dom Type) -> TypeError DefinitionIsIrrelevant :: QName -> TypeError VariableIsIrrelevant :: Name -> TypeError UnequalTerms :: Comparison -> Term -> Term -> Type -> TypeError UnequalTypes :: Comparison -> Type -> Type -> TypeError -- | The two function types have different relevance. UnequalRelevance :: Comparison -> Term -> Term -> TypeError -- | The two function types have different hiding. UnequalHiding :: Term -> Term -> TypeError -- | The two function types have different color. UnequalColors :: Term -> Term -> TypeError UnequalSorts :: Sort -> Sort -> TypeError UnequalBecauseOfUniverseConflict :: Comparison -> Term -> Term -> TypeError -- | We ended up with an equality constraint where the terms have different -- types. This is not supported. HeterogeneousEquality :: Term -> Type -> Term -> Type -> TypeError NotLeqSort :: Sort -> Sort -> TypeError -- | The arguments are the meta variable, the parameters it can depend on -- and the paratemeter that it wants to depend on. MetaCannotDependOn :: MetaId -> [Nat] -> Nat -> TypeError MetaOccursInItself :: MetaId -> TypeError GenericError :: String -> TypeError GenericDocError :: Doc -> TypeError BuiltinMustBeConstructor :: String -> Expr -> TypeError NoSuchBuiltinName :: String -> TypeError DuplicateBuiltinBinding :: String -> Term -> Term -> TypeError NoBindingForBuiltin :: String -> TypeError NoSuchPrimitiveFunction :: String -> TypeError ShadowedModule :: Name -> [ModuleName] -> TypeError BuiltinInParameterisedModule :: String -> TypeError IllegalLetInTelescope :: TypedBinding -> TypeError NoRHSRequiresAbsurdPattern :: [NamedArg Pattern] -> TypeError AbsurdPatternRequiresNoRHS :: [NamedArg Pattern] -> TypeError TooFewFields :: QName -> [Name] -> TypeError TooManyFields :: QName -> [Name] -> TypeError DuplicateFields :: [Name] -> TypeError DuplicateConstructors :: [Name] -> TypeError WithOnFreeVariable :: Expr -> TypeError UnexpectedWithPatterns :: [Pattern] -> TypeError WithClausePatternMismatch :: Pattern -> Pattern -> TypeError FieldOutsideRecord :: TypeError ModuleArityMismatch :: ModuleName -> Telescope -> [NamedArg Expr] -> TypeError IncompletePatternMatching :: Term -> [Elim] -> TypeError CoverageFailure :: QName -> [[Arg Pattern]] -> TypeError UnreachableClauses :: QName -> [[Arg Pattern]] -> TypeError CoverageCantSplitOn :: QName -> Telescope -> Args -> Args -> TypeError CoverageCantSplitIrrelevantType :: Type -> TypeError CoverageCantSplitType :: Type -> TypeError WithoutKError :: Type -> Term -> Term -> TypeError SplitError :: SplitError -> TypeError NotStrictlyPositive :: QName -> [Occ] -> TypeError LocalVsImportedModuleClash :: ModuleName -> TypeError UnsolvedMetas :: [Range] -> TypeError UnsolvedConstraints :: Constraints -> TypeError -- | Some interaction points (holes) have not be filled by user. There are -- not UnsolvedMetas since unification solved them. This is an -- error, since interaction points are never filled without user -- interaction. SolvedButOpenHoles :: TypeError CyclicModuleDependency :: [TopLevelModuleName] -> TypeError FileNotFound :: TopLevelModuleName -> [AbsolutePath] -> TypeError OverlappingProjects :: AbsolutePath -> TopLevelModuleName -> TopLevelModuleName -> TypeError AmbiguousTopLevelModuleName :: TopLevelModuleName -> [AbsolutePath] -> TypeError ModuleNameDoesntMatchFileName :: TopLevelModuleName -> [AbsolutePath] -> TypeError ClashingFileNamesFor :: ModuleName -> [AbsolutePath] -> TypeError -- | Module name, file from which it was loaded, file which the include -- path says contains the module. Scope errors ModuleDefinedInOtherFile :: TopLevelModuleName -> AbsolutePath -> AbsolutePath -> TypeError BothWithAndRHS :: TypeError NotInScope :: [QName] -> TypeError NoSuchModule :: QName -> TypeError AmbiguousName :: QName -> [QName] -> TypeError AmbiguousModule :: QName -> [ModuleName] -> TypeError UninstantiatedModule :: QName -> TypeError ClashingDefinition :: QName -> QName -> TypeError ClashingModule :: ModuleName -> ModuleName -> TypeError ClashingImport :: Name -> QName -> TypeError ClashingModuleImport :: Name -> ModuleName -> TypeError PatternShadowsConstructor :: Name -> QName -> TypeError ModuleDoesntExport :: QName -> [ImportedName] -> TypeError DuplicateImports :: QName -> [ImportedName] -> TypeError InvalidPattern :: Pattern -> TypeError RepeatedVariablesInPattern :: [Name] -> TypeError -- | The expr was used in the right hand side of an implicit module -- definition, but it wasn't of the form m Delta. NotAModuleExpr :: Expr -> TypeError NotAnExpression :: Expr -> TypeError NotAValidLetBinding :: NiceDeclaration -> TypeError NothingAppliedToHiddenArg :: Expr -> TypeError NothingAppliedToInstanceArg :: Expr -> TypeError BadArgumentsToPatternSynonym :: QName -> TypeError TooFewArgumentsToPatternSynonym :: QName -> TypeError UnusedVariableInPatternSynonym :: TypeError NoParseForApplication :: [Expr] -> TypeError AmbiguousParseForApplication :: [Expr] -> [Expr] -> TypeError NoParseForLHS :: LHSOrPatSyn -> Pattern -> TypeError AmbiguousParseForLHS :: LHSOrPatSyn -> Pattern -> [Pattern] -> TypeError IFSNoCandidateInScope :: Type -> TypeError UnquoteFailed :: UnquoteError -> TypeError SafeFlagPostulate :: Name -> TypeError SafeFlagPragma :: [String] -> TypeError SafeFlagNoTerminationCheck :: TypeError SafeFlagNonTerminating :: TypeError SafeFlagTerminating :: TypeError SafeFlagPrimTrustMe :: TypeError NeedOptionCopatterns :: TypeError NeedOptionRewriting :: TypeError -- | Distinguish error message when parsing lhs or pattern synonym, resp. data LHSOrPatSyn IsLHS :: LHSOrPatSyn IsPatSyn :: LHSOrPatSyn -- | Type-checking errors. data TCErr TypeError :: TCState -> (Closure TypeError) -> TCErr Exception :: Range -> Doc -> TCErr IOException :: Range -> IOException -> TCErr PatternErr :: TCErr -- | Environment of the reduce monad. data ReduceEnv ReduceEnv :: TCEnv -> TCState -> ReduceEnv -- | Read only access to environment. [redEnv] :: ReduceEnv -> TCEnv -- | Read only access to state (signature, metas...). [redSt] :: ReduceEnv -> TCState mapRedEnv :: (TCEnv -> TCEnv) -> ReduceEnv -> ReduceEnv mapRedSt :: (TCState -> TCState) -> ReduceEnv -> ReduceEnv mapRedEnvSt :: (TCEnv -> TCEnv) -> (TCState -> TCState) -> ReduceEnv -> ReduceEnv newtype ReduceM a ReduceM :: Reader ReduceEnv a -> ReduceM a [unReduceM] :: ReduceM a -> Reader ReduceEnv a runReduceM :: ReduceM a -> TCM a runReduceF :: (a -> ReduceM b) -> TCM (a -> b) newtype TCMT m a TCM :: (IORef TCState -> TCEnv -> m a) -> TCMT m a [unTCM] :: TCMT m a -> IORef TCState -> TCEnv -> m a type TCM = TCMT IO class (Applicative tcm, MonadIO tcm, MonadReader TCEnv tcm, MonadState TCState tcm) => MonadTCM tcm liftTCM :: MonadTCM tcm => TCM a -> tcm a -- | Interaction monad. type IM = TCMT (InputT IO) runIM :: IM a -> TCM a -- | Preserve the state of the failing computation. catchError_ :: TCM a -> (TCErr -> TCM a) -> TCM a -- | Execute a finalizer even when an exception is thrown. Does not catch -- any errors. In case both the regular computation and the finalizer -- throw an exception, the one of the finalizer is propagated. finally_ :: TCM a -> TCM b -> TCM a mapTCMT :: (forall a. m a -> n a) -> TCMT m a -> TCMT n a pureTCM :: MonadIO m => (TCState -> TCEnv -> a) -> TCMT m a returnTCMT :: MonadIO m => a -> TCMT m a bindTCMT :: MonadIO m => TCMT m a -> (a -> TCMT m b) -> TCMT m b thenTCMT :: MonadIO m => TCMT m a -> TCMT m b -> TCMT m b fmapTCMT :: MonadIO m => (a -> b) -> TCMT m a -> TCMT m b apTCMT :: MonadIO m => TCMT m (a -> b) -> TCMT m a -> TCMT m b -- | We store benchmark statistics in an IORef. This enables benchmarking -- pure computation, see Agda.Benchmarking. -- | Short-cutting disjunction forms a monoid. patternViolation :: TCM a internalError :: MonadTCM tcm => String -> tcm a genericError :: MonadTCM tcm => String -> tcm a typeError :: MonadTCM tcm => TypeError -> tcm a typeError_ :: MonadTCM tcm => TypeError -> tcm TCErr -- | Running the type checking monad (most general form). runTCM :: MonadIO m => TCEnv -> TCState -> TCMT m a -> m (a, TCState) -- | Running the type checking monad on toplevel (with initial state). runTCMTop :: TCM a -> IO (Either TCErr a) runTCMTop' :: MonadIO m => TCMT m a -> m a -- | runSafeTCM runs a safe TCM action (a TCM action -- which cannot fail) in the initial environment. runSafeTCM :: TCM a -> TCState -> IO (a, TCState) -- | Runs the given computation in a separate thread, with a copy of -- the current state and environment. -- -- Note that Agda sometimes uses actual, mutable state. If the -- computation given to forkTCM tries to modify this -- state, then bad things can happen, because accesses are not mutually -- exclusive. The forkTCM function has been added mainly to -- allow the thread to read (a snapshot of) the current state in a -- convenient way. -- -- Note also that exceptions which are raised in the thread are not -- propagated to the parent, so the thread should not do anything -- important. forkTCM :: TCM a -> TCM () -- | Base name for extended lambda patterns extendedLambdaName :: String -- | Name of absurdLambda definitions. absurdLambdaName :: String -- | Check whether we have an definition from an absurd lambda. isAbsurdLambdaName :: QName -> Bool instance GHC.Show.Show Agda.TypeChecking.Monad.Base.TypeError instance GHC.Show.Show Agda.TypeChecking.Monad.Base.TerminationError instance GHC.Show.Show Agda.TypeChecking.Monad.Base.SplitError instance Agda.Utils.Null.Null Agda.TypeChecking.Monad.Base.Fields instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Occ instance GHC.Show.Show Agda.TypeChecking.Monad.Base.OccPos instance GHC.Show.Show Agda.TypeChecking.Monad.Base.UnquoteError instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Constraint instance GHC.Show.Show Agda.TypeChecking.Monad.Base.ProblemConstraint instance GHC.Base.Functor (Agda.TypeChecking.Monad.Base.Reduced no) instance GHC.Base.Functor Agda.TypeChecking.Monad.Base.MaybeReduced instance GHC.Base.Monad Agda.TypeChecking.Monad.Base.ReduceM instance GHC.Base.Applicative Agda.TypeChecking.Monad.Base.ReduceM instance GHC.Base.Functor Agda.TypeChecking.Monad.Base.ReduceM instance Data.Traversable.Traversable Agda.TypeChecking.Monad.Base.Builtin instance Data.Foldable.Foldable Agda.TypeChecking.Monad.Base.Builtin instance GHC.Base.Functor Agda.TypeChecking.Monad.Base.Builtin instance GHC.Show.Show pf => GHC.Show.Show (Agda.TypeChecking.Monad.Base.Builtin pf) instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Interface instance GHC.Num.Num Agda.TypeChecking.Monad.Base.ProblemId instance GHC.Real.Integral Agda.TypeChecking.Monad.Base.ProblemId instance GHC.Real.Real Agda.TypeChecking.Monad.Base.ProblemId instance GHC.Enum.Enum Agda.TypeChecking.Monad.Base.ProblemId instance GHC.Classes.Ord Agda.TypeChecking.Monad.Base.ProblemId instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.ProblemId instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Section instance GHC.Show.Show Agda.TypeChecking.Monad.Base.DisplayTerm instance GHC.Show.Show Agda.TypeChecking.Monad.Base.DisplayForm instance GHC.Show.Show Agda.TypeChecking.Monad.Base.HaskellRepresentation instance GHC.Show.Show Agda.TypeChecking.Monad.Base.HaskellExport instance GHC.Show.Show Agda.TypeChecking.Monad.Base.CompiledRepresentation instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Projection instance GHC.Show.Show Agda.TypeChecking.Monad.Base.TermHead instance GHC.Classes.Ord Agda.TypeChecking.Monad.Base.TermHead instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.TermHead instance GHC.Base.Functor Agda.TypeChecking.Monad.Base.FunctionInverse' instance GHC.Show.Show c => GHC.Show.Show (Agda.TypeChecking.Monad.Base.FunctionInverse' c) instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Defn instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Definition instance GHC.Show.Show Agda.TypeChecking.Monad.Base.NLPat instance GHC.Show.Show Agda.TypeChecking.Monad.Base.RewriteRule instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Signature instance GHC.Num.Num Agda.TypeChecking.Monad.Base.CtxId instance GHC.Real.Integral Agda.TypeChecking.Monad.Base.CtxId instance GHC.Real.Real Agda.TypeChecking.Monad.Base.CtxId instance GHC.Enum.Enum Agda.TypeChecking.Monad.Base.CtxId instance GHC.Show.Show Agda.TypeChecking.Monad.Base.CtxId instance GHC.Classes.Ord Agda.TypeChecking.Monad.Base.CtxId instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.CtxId instance GHC.Base.Functor Agda.TypeChecking.Monad.Base.Open instance GHC.Show.Show a => GHC.Show.Show (Agda.TypeChecking.Monad.Base.Open a) instance GHC.Show.Show Agda.TypeChecking.Monad.Base.LHSOrPatSyn instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.LHSOrPatSyn instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.ExpandInstances instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.ExpandHidden instance GHC.Show.Show Agda.TypeChecking.Monad.Base.AbstractMode instance GHC.Read.Read Agda.TypeChecking.Monad.Base.HighlightingMethod instance GHC.Show.Show Agda.TypeChecking.Monad.Base.HighlightingMethod instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.HighlightingMethod instance GHC.Read.Read Agda.TypeChecking.Monad.Base.HighlightingLevel instance GHC.Show.Show Agda.TypeChecking.Monad.Base.HighlightingLevel instance GHC.Classes.Ord Agda.TypeChecking.Monad.Base.HighlightingLevel instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.HighlightingLevel instance GHC.Enum.Enum Agda.TypeChecking.Monad.Base.MutualId instance GHC.Num.Num Agda.TypeChecking.Monad.Base.MutualId instance GHC.Show.Show Agda.TypeChecking.Monad.Base.MutualId instance GHC.Classes.Ord Agda.TypeChecking.Monad.Base.MutualId instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.MutualId instance GHC.Enum.Bounded Agda.TypeChecking.Monad.Base.AllowedReduction instance GHC.Enum.Enum Agda.TypeChecking.Monad.Base.AllowedReduction instance GHC.Classes.Ord Agda.TypeChecking.Monad.Base.AllowedReduction instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.AllowedReduction instance GHC.Show.Show Agda.TypeChecking.Monad.Base.AllowedReduction instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Simplification instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.Simplification instance GHC.Show.Show Agda.TypeChecking.Monad.Base.ExtLamInfo instance GHC.Classes.Ord Agda.TypeChecking.Monad.Base.ExtLamInfo instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.ExtLamInfo instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.Polarity instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Polarity instance GHC.Show.Show Agda.TypeChecking.Monad.Base.RunMetaOccursCheck instance GHC.Classes.Ord Agda.TypeChecking.Monad.Base.RunMetaOccursCheck instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.RunMetaOccursCheck instance GHC.Show.Show Agda.TypeChecking.Monad.Base.MetaPriority instance GHC.Classes.Ord Agda.TypeChecking.Monad.Base.MetaPriority instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.MetaPriority instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Frozen instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.Frozen instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.CompareDirection instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.Comparison instance Agda.TypeChecking.Monad.Base.HasFresh Agda.Syntax.Common.MetaId instance Agda.TypeChecking.Monad.Base.HasFresh Agda.TypeChecking.Monad.Base.MutualId instance Agda.TypeChecking.Monad.Base.HasFresh Agda.Syntax.Common.InteractionId instance Agda.TypeChecking.Monad.Base.HasFresh Agda.Syntax.Common.NameId instance Agda.TypeChecking.Monad.Base.HasFresh Agda.TypeChecking.Monad.Base.CtxId instance Agda.TypeChecking.Monad.Base.HasFresh GHC.Types.Int instance GHC.Show.Show Agda.TypeChecking.Monad.Base.ProblemId instance Agda.Utils.Pretty.Pretty Agda.TypeChecking.Monad.Base.ProblemId instance Agda.TypeChecking.Monad.Base.HasFresh Agda.TypeChecking.Monad.Base.ProblemId instance Agda.TypeChecking.Monad.Base.FreshName (Agda.Syntax.Position.Range, GHC.Base.String) instance Agda.TypeChecking.Monad.Base.FreshName GHC.Base.String instance Agda.TypeChecking.Monad.Base.FreshName Agda.Syntax.Position.Range instance Agda.TypeChecking.Monad.Base.FreshName () instance Agda.Utils.Pretty.Pretty Agda.TypeChecking.Monad.Base.Interface instance GHC.Show.Show a => GHC.Show.Show (Agda.TypeChecking.Monad.Base.Closure a) instance Agda.Syntax.Position.HasRange a => Agda.Syntax.Position.HasRange (Agda.TypeChecking.Monad.Base.Closure a) instance Agda.Syntax.Position.HasRange Agda.TypeChecking.Monad.Base.ProblemConstraint instance Agda.Syntax.Position.HasRange Agda.TypeChecking.Monad.Base.Constraint instance GHC.Show.Show Agda.TypeChecking.Monad.Base.Comparison instance Agda.Utils.Pretty.Pretty Agda.TypeChecking.Monad.Base.Comparison instance GHC.Show.Show Agda.TypeChecking.Monad.Base.CompareDirection instance GHC.Show.Show a => GHC.Show.Show (Agda.TypeChecking.Monad.Base.Judgement a) instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.Listener instance GHC.Classes.Ord Agda.TypeChecking.Monad.Base.Listener instance GHC.Show.Show Agda.TypeChecking.Monad.Base.MetaInstantiation instance Agda.Utils.Pretty.Pretty Agda.TypeChecking.Monad.Base.NamedMeta instance Agda.Syntax.Position.HasRange Agda.TypeChecking.Monad.Base.MetaInfo instance Agda.Syntax.Position.HasRange Agda.TypeChecking.Monad.Base.MetaVariable instance Agda.Syntax.Position.SetRange Agda.TypeChecking.Monad.Base.MetaInfo instance Agda.Syntax.Position.SetRange Agda.TypeChecking.Monad.Base.MetaVariable instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.InteractionPoint instance Agda.Utils.Null.Null Agda.TypeChecking.Monad.Base.Simplification instance GHC.Base.Monoid Agda.TypeChecking.Monad.Base.Simplification instance Agda.Syntax.Internal.IsProjElim e => Agda.Syntax.Internal.IsProjElim (Agda.TypeChecking.Monad.Base.MaybeReduced e) instance Agda.Utils.Pretty.Pretty Agda.TypeChecking.Monad.Base.Call instance Agda.Syntax.Position.HasRange Agda.TypeChecking.Monad.Base.Call instance GHC.Show.Show Agda.TypeChecking.Monad.Base.CallInfo instance Agda.Utils.Pretty.Pretty Agda.TypeChecking.Monad.Base.CallInfo instance Agda.Syntax.Abstract.AllNames Agda.TypeChecking.Monad.Base.CallInfo instance Agda.Utils.Except.Error Agda.TypeChecking.Monad.Base.SplitError instance Agda.Utils.Except.Error Agda.TypeChecking.Monad.Base.UnquoteError instance Agda.Utils.Except.Error Agda.TypeChecking.Monad.Base.TCErr instance GHC.Show.Show Agda.TypeChecking.Monad.Base.TCErr instance Agda.Syntax.Position.HasRange Agda.TypeChecking.Monad.Base.TCErr instance GHC.Exception.Exception Agda.TypeChecking.Monad.Base.TCErr instance Control.Monad.Reader.Class.MonadReader Agda.TypeChecking.Monad.Base.TCEnv Agda.TypeChecking.Monad.Base.ReduceM instance Control.Monad.IO.Class.MonadIO m => Control.Monad.Reader.Class.MonadReader Agda.TypeChecking.Monad.Base.TCEnv (Agda.TypeChecking.Monad.Base.TCMT m) instance Control.Monad.IO.Class.MonadIO m => Control.Monad.State.Class.MonadState Agda.TypeChecking.Monad.Base.TCState (Agda.TypeChecking.Monad.Base.TCMT m) instance Control.Monad.Error.Class.MonadError Agda.TypeChecking.Monad.Base.TCErr (Agda.TypeChecking.Monad.Base.TCMT GHC.Types.IO) instance Control.Monad.Error.Class.MonadError Agda.TypeChecking.Monad.Base.TCErr Agda.TypeChecking.Monad.Base.IM instance Control.Monad.IO.Class.MonadIO m => Agda.TypeChecking.Monad.Base.MonadTCM (Agda.TypeChecking.Monad.Base.TCMT m) instance Agda.TypeChecking.Monad.Base.MonadTCM tcm => Agda.TypeChecking.Monad.Base.MonadTCM (Control.Monad.Trans.Maybe.MaybeT tcm) instance Agda.TypeChecking.Monad.Base.MonadTCM tcm => Agda.TypeChecking.Monad.Base.MonadTCM (Agda.Utils.ListT.ListT tcm) instance (Agda.Utils.Except.Error err, Agda.TypeChecking.Monad.Base.MonadTCM tcm) => Agda.TypeChecking.Monad.Base.MonadTCM (Control.Monad.Trans.Except.ExceptT err tcm) instance (GHC.Base.Monoid w, Agda.TypeChecking.Monad.Base.MonadTCM tcm) => Agda.TypeChecking.Monad.Base.MonadTCM (Control.Monad.Trans.Writer.Lazy.WriterT w tcm) instance Control.Monad.Trans.Class.MonadTrans Agda.TypeChecking.Monad.Base.TCMT instance Control.Monad.IO.Class.MonadIO m => GHC.Base.Monad (Agda.TypeChecking.Monad.Base.TCMT m) instance Control.Monad.IO.Class.MonadIO m => GHC.Base.Functor (Agda.TypeChecking.Monad.Base.TCMT m) instance Control.Monad.IO.Class.MonadIO m => GHC.Base.Applicative (Agda.TypeChecking.Monad.Base.TCMT m) instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Agda.TypeChecking.Monad.Base.TCMT m) instance Agda.Utils.Benchmark.MonadBench Agda.Benchmarking.Phase Agda.TypeChecking.Monad.Base.TCM instance Agda.Utils.Null.Null (Agda.TypeChecking.Monad.Base.TCM Text.PrettyPrint.HughesPJ.Doc) instance GHC.Base.Monoid (Agda.TypeChecking.Monad.Base.TCM Data.Monoid.Any) instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.Signature instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.Sections instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.Definitions instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.RewriteRuleMap instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.Section instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.Definition instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.NLPat instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.RewriteRule instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.CompiledRepresentation instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.ExtLamInfo instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.Defn instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.MutualId instance Agda.Syntax.Position.KillRange c => Agda.Syntax.Position.KillRange (Agda.TypeChecking.Monad.Base.FunctionInverse' c) instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.TermHead instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.Projection instance Agda.Syntax.Position.KillRange a => Agda.Syntax.Position.KillRange (Agda.TypeChecking.Monad.Base.Open a) instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.DisplayForm instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.Polarity instance Agda.Syntax.Position.KillRange Agda.TypeChecking.Monad.Base.DisplayTerm module Agda.TypeChecking.Substitute -- | Apply something to a bunch of arguments. Preserves blocking tags -- (application can never resolve blocking). class Apply t where apply t args = applyE t $ map Apply args applyE t es = apply t $ map argFromElim es apply :: Apply t => t -> Args -> t applyE :: Apply t => t -> Elims -> t -- | Apply to a single argument. apply1 :: Apply t => t -> Term -> t -- | If $v$ is a record value, canProject f v returns its field -- f. canProject :: QName -> Term -> Maybe (Arg Term) -- | Eliminate a constructed term. conApp :: ConHead -> Args -> Elims -> Term -- | defApp f us vs applies Def f us to further arguments -- vs, eliminating top projection redexes. If us is not -- empty, we cannot have a projection redex, since the record argument is -- the first one. defApp :: QName -> Elims -> Elims -> Term argToDontCare :: Arg c Term -> Term -- | The type must contain the right number of pis without have to perform -- any reduction. piApply :: Type -> Args -> Type -- | (abstract args v) apply args --> v[args]. class Abstract t abstract :: Abstract t => Telescope -> t -> t -- | tel ⊢ (Γ ⊢ lhs ↦ rhs : t) becomes tel, Γ ⊢ lhs ↦ rhs : -- t) we do not need to change lhs, rhs, and t since they live in Γ. -- See 'Abstract Clause'. telVars :: Telescope -> [Arg Pattern] namedTelVars :: Telescope -> [NamedArg Pattern] abstractArgs :: Abstract a => Args -> a -> a idS :: Substitution wkS :: Int -> Substitution -> Substitution raiseS :: Int -> Substitution consS :: Term -> Substitution -> Substitution -- | To replace index n by term u, do applySubst -- (singletonS n u). singletonS :: Int -> Term -> Substitution -- | Lift a substitution under k binders. liftS :: Int -> Substitution -> Substitution dropS :: Int -> Substitution -> Substitution -- |
--   applySubst (ρ composeS σ) v == applySubst ρ (applySubst σ v)
--   
composeS :: Substitution -> Substitution -> Substitution splitS :: Int -> Substitution -> (Substitution, Substitution) (++#) :: [Term] -> Substitution -> Substitution prependS :: Empty -> [Maybe Term] -> Substitution -> Substitution parallelS :: [Term] -> Substitution compactS :: Empty -> [Maybe Term] -> Substitution -- | Γ ⊢ (strengthenS ⊥ |Δ|) : Γ,Δ strengthenS :: Empty -> Int -> Substitution lookupS :: Substitution -> Nat -> Term -- | Apply a substitution. class Subst t applySubst :: Subst t => Substitution -> t -> t raise :: Subst t => Nat -> t -> t raiseFrom :: Subst t => Nat -> Nat -> t -> t -- | Replace de Bruijn index i by a Term in something. subst :: Subst t => Int -> Term -> t -> t strengthen :: Subst t => Empty -> t -> t -- | Replace what is now de Bruijn index 0, but go under n binders. -- substUnder n u == subst n (raise n u). substUnder :: Subst t => Nat -> Term -> t -> t type TelView = TelV Type data TelV a TelV :: Tele (Dom a) -> a -> TelV a [theTel] :: TelV a -> Tele (Dom a) [theCore] :: TelV a -> a type ListTel' a = [Dom (a, Type)] type ListTel = ListTel' ArgName telFromList' :: (a -> ArgName) -> ListTel' a -> Telescope telFromList :: ListTel -> Telescope telToList :: Telescope -> ListTel telToArgs :: Telescope -> [Arg ArgName] -- | Turn a typed binding (x1 .. xn : A) into a telescope. bindsToTel' :: (Name -> a) -> [Name] -> Dom Type -> ListTel' a bindsToTel :: [Name] -> Dom Type -> ListTel -- | Turn a typed binding (x1 .. xn : A) into a telescope. bindsWithHidingToTel' :: (Name -> a) -> [WithHiding Name] -> Dom Type -> ListTel' a bindsWithHidingToTel :: [WithHiding Name] -> Dom Type -> ListTel -- | Takes off all exposed function domains from the given type. This means -- that it does not reduce to expose Pi-types. telView' :: Type -> TelView -- | telView'UpTo n t takes off the first n exposed -- function types of t. Takes off all (exposed ones) if n -- < 0. telView'UpTo :: Int -> Type -> TelView -- |
--   mkPi dom t = telePi (telFromList [dom]) t
--   
mkPi :: Dom (ArgName, Type) -> Type -> Type mkLam :: Arg ArgName -> Term -> Term telePi' :: (Abs Type -> Abs Type) -> Telescope -> Type -> Type -- | Uses free variable analysis to introduce noAbs bindings. telePi :: Telescope -> Type -> Type -- | Everything will be a Abs. telePi_ :: Telescope -> Type -> Type teleLam :: Telescope -> Term -> Term -- | Performs void (noAbs) abstraction over telescope. class TeleNoAbs a teleNoAbs :: TeleNoAbs a => a -> Term -> Term -- | Dependent least upper bound, to assign a level to expressions like -- forall i -> Set i. -- -- dLub s1 i.s2 = omega if i appears in the rigid -- variables of s2. dLub :: Sort -> Abs Sort -> Sort -- | Instantiate an abstraction. Strict in the term. absApp :: Subst t => Abs t -> Term -> t -- | Instantiate an abstraction. Lazy in the term, which allow it to be -- IMPOSSIBLE in the case where the variable shouldn't be used but -- we cannot use noabsApp. Used in Apply. lazyAbsApp :: Subst t => Abs t -> Term -> t -- | Instantiate an abstraction that doesn't use its argument. noabsApp :: Subst t => Empty -> Abs t -> t absBody :: Subst t => Abs t -> t mkAbs :: (Subst a, Free a) => ArgName -> a -> Abs a reAbs :: (Subst a, Free a) => Abs a -> Abs a -- | underAbs k a b applies k to a and the -- content of abstraction b and puts the abstraction back. -- a is raised if abstraction was proper such that at point of -- application of k and the content of b are at the -- same context. Precondition: a and b are at the same -- context at call time. underAbs :: Subst a => (a -> b -> b) -> a -> Abs b -> Abs b -- | underLambdas n k a b drops n initial Lams -- from b, performs operation k on a and the -- body of b, and puts the Lams back. a is -- raised correctly according to the number of abstractions. underLambdas :: Subst a => Int -> (a -> Term -> Term) -> a -> Term -> Term -- | Methods to retrieve the clauseBody. class GetBody a -- | Returns the properly raised clause Body, and Nothing if -- NoBody. getBody :: GetBody a => a -> Maybe Term -- | Just grabs the body, without raising the de Bruijn indices. This is -- useful if you want to consider the body in context clauseTel. getBodyUnraised :: GetBody a => a -> Maybe Term -- | Syntactic Type equality, ignores sort annotations. -- | Syntactic Term equality, ignores stuff below DontCare -- and sharing. -- | The `rule', if Agda is considered as a functional pure type -- system (pts). -- -- TODO: This needs to be properly implemented, requiring refactoring of -- Agda's handling of levels. Without impredicativity or SizeUniv, -- Agda's pts rule is just the least upper bound, which is total and -- commutative. The handling of levels relies on this simplification. pts :: Sort -> Sort -> Sort sLub :: Sort -> Sort -> Sort lvlView :: Term -> Level levelMax :: [PlusLevel] -> Level sortTm :: Sort -> Term levelSort :: Level -> Sort levelTm :: Level -> Term unLevelAtom :: LevelAtom -> Term -- | Substitutions. data Substitution -- | Identity substitution. Γ ⊢ IdS : Γ IdS :: Substitution -- | Empty substitution, lifts from the empty context. Apply this to closed -- terms you want to use in a non-empty context. Γ ⊢ EmptyS : () EmptyS :: Substitution -- | Substitution extension, `cons'. Γ ⊢ u : Aρ Γ ⊢ ρ : Δ -- ---------------------- Γ ⊢ u :# ρ : Δ, A (:#) :: Term -> Substitution -> Substitution -- | Strengthening substitution. First argument is -- IMPOSSIBLE. Apply this to a term which does not -- contain variable 0 to lower all de Bruijn indices by one. Γ ⊢ ρ : -- Δ --------------------------- Γ ⊢ Strengthen ρ : Δ, A Strengthen :: Empty -> Substitution -> Substitution -- | Weakning substitution, lifts to an extended context. Γ ⊢ ρ : Δ -- ------------------- Γ, Ψ ⊢ Wk |Ψ| ρ : Δ Wk :: !Int -> Substitution -> Substitution -- | Lifting substitution. Use this to go under a binder. Lift 1 ρ == -- var 0 :# Wk 1 ρ. Γ ⊢ ρ : Δ ------------------------- Γ, Ψρ ⊢ -- Lift |Ψ| ρ : Δ, Ψ Lift :: !Int -> Substitution -> Substitution instance GHC.Base.Functor Agda.TypeChecking.Substitute.TelV instance (GHC.Classes.Ord a, Agda.TypeChecking.Substitute.Subst a) => GHC.Classes.Ord (Agda.TypeChecking.Substitute.TelV a) instance (GHC.Classes.Eq a, Agda.TypeChecking.Substitute.Subst a) => GHC.Classes.Eq (Agda.TypeChecking.Substitute.TelV a) instance GHC.Show.Show a => GHC.Show.Show (Agda.TypeChecking.Substitute.TelV a) instance GHC.Classes.Eq Agda.Syntax.Internal.Substitution instance GHC.Classes.Ord Agda.Syntax.Internal.Substitution instance GHC.Classes.Eq Agda.Syntax.Internal.Sort instance GHC.Classes.Ord Agda.Syntax.Internal.Sort instance GHC.Classes.Eq Agda.Syntax.Internal.Level instance GHC.Classes.Ord Agda.Syntax.Internal.Level instance GHC.Classes.Eq Agda.Syntax.Internal.PlusLevel instance GHC.Classes.Ord Agda.Syntax.Internal.LevelAtom instance GHC.Classes.Eq Agda.Syntax.Internal.NotBlocked instance GHC.Classes.Ord Agda.Syntax.Internal.NotBlocked instance GHC.Classes.Eq t => GHC.Classes.Eq (Agda.Syntax.Internal.Blocked t) instance GHC.Classes.Ord t => GHC.Classes.Ord (Agda.Syntax.Internal.Blocked t) instance (Agda.TypeChecking.Substitute.Subst a, GHC.Classes.Eq a) => GHC.Classes.Eq (Agda.Syntax.Internal.Elim' a) instance (Agda.TypeChecking.Substitute.Subst a, GHC.Classes.Ord a) => GHC.Classes.Ord (Agda.Syntax.Internal.Elim' a) instance (Agda.TypeChecking.Substitute.Subst a, GHC.Classes.Eq a) => GHC.Classes.Eq (Agda.Syntax.Internal.Tele a) instance (Agda.TypeChecking.Substitute.Subst a, GHC.Classes.Ord a) => GHC.Classes.Ord (Agda.Syntax.Internal.Tele a) instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.Constraint instance GHC.Classes.Eq Agda.TypeChecking.Monad.Base.Section instance Agda.TypeChecking.Substitute.Apply Agda.Syntax.Internal.Term instance Agda.TypeChecking.Substitute.Apply Agda.Syntax.Internal.Type instance Agda.TypeChecking.Substitute.Apply Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Substitute.Apply a => Agda.TypeChecking.Substitute.Apply (Agda.Utils.Pointer.Ptr a) instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Apply (Agda.Syntax.Internal.Tele a) instance Agda.TypeChecking.Substitute.Apply Agda.TypeChecking.Monad.Base.Definition instance Agda.TypeChecking.Substitute.Apply Agda.TypeChecking.Monad.Base.RewriteRule instance Agda.TypeChecking.Substitute.Apply [Agda.TypeChecking.Positivity.Occurrence.Occurrence] instance Agda.TypeChecking.Substitute.Apply [Agda.TypeChecking.Monad.Base.Polarity] instance Agda.TypeChecking.Substitute.Apply Agda.TypeChecking.Monad.Base.Projection instance Agda.TypeChecking.Substitute.Apply Agda.TypeChecking.Monad.Base.Defn instance Agda.TypeChecking.Substitute.Apply Agda.TypeChecking.Monad.Base.PrimFun instance Agda.TypeChecking.Substitute.Apply Agda.Syntax.Internal.Clause instance Agda.TypeChecking.Substitute.Apply Agda.TypeChecking.CompiledClause.CompiledClauses instance Agda.TypeChecking.Substitute.Apply a => Agda.TypeChecking.Substitute.Apply (Agda.TypeChecking.CompiledClause.WithArity a) instance Agda.TypeChecking.Substitute.Apply a => Agda.TypeChecking.Substitute.Apply (Agda.TypeChecking.CompiledClause.Case a) instance Agda.TypeChecking.Substitute.Apply Agda.TypeChecking.Monad.Base.FunctionInverse instance Agda.TypeChecking.Substitute.Apply Agda.Syntax.Internal.ClauseBody instance Agda.TypeChecking.Substitute.Apply Agda.TypeChecking.Monad.Base.DisplayTerm instance Agda.TypeChecking.Substitute.Apply t => Agda.TypeChecking.Substitute.Apply [t] instance Agda.TypeChecking.Substitute.Apply t => Agda.TypeChecking.Substitute.Apply (Agda.Syntax.Internal.Blocked t) instance Agda.TypeChecking.Substitute.Apply t => Agda.TypeChecking.Substitute.Apply (GHC.Base.Maybe t) instance Agda.TypeChecking.Substitute.Apply v => Agda.TypeChecking.Substitute.Apply (Data.Map.Base.Map k v) instance (Agda.TypeChecking.Substitute.Apply a, Agda.TypeChecking.Substitute.Apply b) => Agda.TypeChecking.Substitute.Apply (a, b) instance (Agda.TypeChecking.Substitute.Apply a, Agda.TypeChecking.Substitute.Apply b, Agda.TypeChecking.Substitute.Apply c) => Agda.TypeChecking.Substitute.Apply (a, b, c) instance Agda.Utils.Permutation.DoDrop a => Agda.TypeChecking.Substitute.Apply (Agda.Utils.Permutation.Drop a) instance Agda.Utils.Permutation.DoDrop a => Agda.TypeChecking.Substitute.Abstract (Agda.Utils.Permutation.Drop a) instance Agda.TypeChecking.Substitute.Apply Agda.Utils.Permutation.Permutation instance Agda.TypeChecking.Substitute.Abstract Agda.Utils.Permutation.Permutation instance Agda.TypeChecking.Substitute.Abstract Agda.Syntax.Internal.Term instance Agda.TypeChecking.Substitute.Abstract Agda.Syntax.Internal.Type instance Agda.TypeChecking.Substitute.Abstract Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Substitute.Abstract Agda.Syntax.Internal.Telescope instance Agda.TypeChecking.Substitute.Abstract Agda.TypeChecking.Monad.Base.Definition instance Agda.TypeChecking.Substitute.Abstract Agda.TypeChecking.Monad.Base.RewriteRule instance Agda.TypeChecking.Substitute.Abstract [Agda.TypeChecking.Positivity.Occurrence.Occurrence] instance Agda.TypeChecking.Substitute.Abstract [Agda.TypeChecking.Monad.Base.Polarity] instance Agda.TypeChecking.Substitute.Abstract Agda.TypeChecking.Monad.Base.Projection instance Agda.TypeChecking.Substitute.Abstract Agda.TypeChecking.Monad.Base.Defn instance Agda.TypeChecking.Substitute.Abstract Agda.TypeChecking.Monad.Base.PrimFun instance Agda.TypeChecking.Substitute.Abstract Agda.Syntax.Internal.Clause instance Agda.TypeChecking.Substitute.Abstract Agda.TypeChecking.CompiledClause.CompiledClauses instance Agda.TypeChecking.Substitute.Abstract a => Agda.TypeChecking.Substitute.Abstract (Agda.TypeChecking.CompiledClause.WithArity a) instance Agda.TypeChecking.Substitute.Abstract a => Agda.TypeChecking.Substitute.Abstract (Agda.TypeChecking.CompiledClause.Case a) instance Agda.TypeChecking.Substitute.Abstract Agda.TypeChecking.Monad.Base.FunctionInverse instance Agda.TypeChecking.Substitute.Abstract Agda.Syntax.Internal.ClauseBody instance Agda.TypeChecking.Substitute.Abstract t => Agda.TypeChecking.Substitute.Abstract [t] instance Agda.TypeChecking.Substitute.Abstract t => Agda.TypeChecking.Substitute.Abstract (GHC.Base.Maybe t) instance Agda.TypeChecking.Substitute.Abstract v => Agda.TypeChecking.Substitute.Abstract (Data.Map.Base.Map k v) instance Agda.TypeChecking.Substitute.Subst Agda.Syntax.Internal.Substitution instance Agda.TypeChecking.Substitute.Subst Agda.Syntax.Internal.Term instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Subst (Agda.Utils.Pointer.Ptr a) instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Subst (Agda.Syntax.Internal.Type' a) instance Agda.TypeChecking.Substitute.Subst Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Substitute.Subst Agda.Syntax.Internal.Level instance Agda.TypeChecking.Substitute.Subst Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Substitute.Subst Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.Substitute.Subst GHC.Types.Bool instance Agda.TypeChecking.Substitute.Subst GHC.Base.String instance Agda.TypeChecking.Substitute.Subst Agda.Syntax.Abstract.Name.Name instance Agda.TypeChecking.Substitute.Subst Agda.Syntax.Internal.ConPatternInfo instance Agda.TypeChecking.Substitute.Subst Agda.Syntax.Internal.Pattern instance Agda.TypeChecking.Substitute.Subst Agda.TypeChecking.Monad.Base.NLPat instance Agda.TypeChecking.Substitute.Subst t => Agda.TypeChecking.Substitute.Subst (Agda.Syntax.Internal.Blocked t) instance Agda.TypeChecking.Substitute.Subst Agda.TypeChecking.Monad.Base.DisplayForm instance Agda.TypeChecking.Substitute.Subst Agda.TypeChecking.Monad.Base.DisplayTerm instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Subst (Agda.Syntax.Internal.Tele a) instance Agda.TypeChecking.Substitute.Subst Agda.TypeChecking.Monad.Base.Constraint instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Subst (Agda.Syntax.Internal.Elim' a) instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Subst (Agda.Syntax.Internal.Abs a) instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Subst (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Subst (Agda.Syntax.Common.Named name a) instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Subst (Agda.Syntax.Internal.Dom a) instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Subst (GHC.Base.Maybe a) instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Subst [a] instance Agda.TypeChecking.Substitute.Subst () instance (Agda.TypeChecking.Substitute.Subst a, Agda.TypeChecking.Substitute.Subst b) => Agda.TypeChecking.Substitute.Subst (a, b) instance (Agda.TypeChecking.Substitute.Subst a, Agda.TypeChecking.Substitute.Subst b, Agda.TypeChecking.Substitute.Subst c) => Agda.TypeChecking.Substitute.Subst (a, b, c) instance (Agda.TypeChecking.Substitute.Subst a, Agda.TypeChecking.Substitute.Subst b, Agda.TypeChecking.Substitute.Subst c, Agda.TypeChecking.Substitute.Subst d) => Agda.TypeChecking.Substitute.Subst (a, b, c, d) instance Agda.TypeChecking.Substitute.Subst Agda.Syntax.Internal.ClauseBody instance Agda.TypeChecking.Substitute.Subst Agda.Syntax.Internal.Clause instance Agda.TypeChecking.Substitute.TeleNoAbs Agda.TypeChecking.Substitute.ListTel instance Agda.TypeChecking.Substitute.TeleNoAbs Agda.Syntax.Internal.Telescope instance Agda.TypeChecking.Substitute.GetBody Agda.Syntax.Internal.ClauseBody instance Agda.TypeChecking.Substitute.GetBody Agda.Syntax.Internal.Clause instance GHC.Classes.Ord Agda.Syntax.Internal.PlusLevel instance GHC.Classes.Eq Agda.Syntax.Internal.LevelAtom instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Syntax.Internal.Type' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Syntax.Internal.Type' a) instance GHC.Classes.Eq Agda.Syntax.Internal.Term instance GHC.Classes.Ord Agda.Syntax.Internal.Term instance (Agda.TypeChecking.Substitute.Subst a, GHC.Classes.Eq a) => GHC.Classes.Eq (Agda.Syntax.Internal.Abs a) instance (Agda.TypeChecking.Substitute.Subst a, GHC.Classes.Ord a) => GHC.Classes.Ord (Agda.Syntax.Internal.Abs a) -- | Functions for abstracting terms over other terms. module Agda.TypeChecking.Abstract piAbstractTerm :: Term -> Type -> Type -> Type -- | isPrefixOf u v = Just es if v == u applyE es. class IsPrefixOf a isPrefixOf :: IsPrefixOf a => a -> a -> Maybe Elims class AbstractTerm a -- |
--   subst u . abstractTerm u == id
--   
abstractTerm :: AbstractTerm a => Term -> a -> a instance Agda.TypeChecking.Abstract.IsPrefixOf Agda.Syntax.Internal.Elims instance Agda.TypeChecking.Abstract.IsPrefixOf Agda.Syntax.Internal.Args instance Agda.TypeChecking.Abstract.IsPrefixOf Agda.Syntax.Internal.Term instance Agda.TypeChecking.Abstract.AbstractTerm Agda.Syntax.Internal.Term instance Agda.TypeChecking.Abstract.AbstractTerm a => Agda.TypeChecking.Abstract.AbstractTerm (Agda.Utils.Pointer.Ptr a) instance Agda.TypeChecking.Abstract.AbstractTerm Agda.Syntax.Internal.Type instance Agda.TypeChecking.Abstract.AbstractTerm Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Abstract.AbstractTerm Agda.Syntax.Internal.Level instance Agda.TypeChecking.Abstract.AbstractTerm Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Abstract.AbstractTerm Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.Abstract.AbstractTerm a => Agda.TypeChecking.Abstract.AbstractTerm (Agda.Syntax.Internal.Elim' a) instance Agda.TypeChecking.Abstract.AbstractTerm a => Agda.TypeChecking.Abstract.AbstractTerm (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.Abstract.AbstractTerm a => Agda.TypeChecking.Abstract.AbstractTerm (Agda.Syntax.Internal.Dom a) instance Agda.TypeChecking.Abstract.AbstractTerm a => Agda.TypeChecking.Abstract.AbstractTerm [a] instance Agda.TypeChecking.Abstract.AbstractTerm a => Agda.TypeChecking.Abstract.AbstractTerm (GHC.Base.Maybe a) instance (Agda.TypeChecking.Substitute.Subst a, Agda.TypeChecking.Abstract.AbstractTerm a) => Agda.TypeChecking.Abstract.AbstractTerm (Agda.Syntax.Internal.Abs a) instance (Agda.TypeChecking.Abstract.AbstractTerm a, Agda.TypeChecking.Abstract.AbstractTerm b) => Agda.TypeChecking.Abstract.AbstractTerm (a, b) module Agda.TypeChecking.Test.Generators data TermConfiguration TermConf :: [QName] -> [QName] -> [QName] -> [Nat] -> UseLiterals -> Frequencies -> Maybe Int -> Bool -> TermConfiguration [tcDefinedNames] :: TermConfiguration -> [QName] [tcConstructorNames] :: TermConfiguration -> [QName] [tcProjectionNames] :: TermConfiguration -> [QName] [tcFreeVariables] :: TermConfiguration -> [Nat] [tcLiterals] :: TermConfiguration -> UseLiterals [tcFrequencies] :: TermConfiguration -> Frequencies -- | Maximum size of the generated element. When Nothing this -- value is initialized from the size parameter. [tcFixSize] :: TermConfiguration -> Maybe Int -- | When this is true no lambdas, literals, or constructors are generated [tcIsType] :: TermConfiguration -> Bool data Frequencies Freqs :: HiddenFreqs -> ElimFreqs -> SortFreqs -> TermFreqs -> Frequencies [hiddenFreqs] :: Frequencies -> HiddenFreqs [elimFreqs] :: Frequencies -> ElimFreqs [sortFreqs] :: Frequencies -> SortFreqs [termFreqs] :: Frequencies -> TermFreqs data TermFreqs TermFreqs :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> TermFreqs [varFreq] :: TermFreqs -> Int [defFreq] :: TermFreqs -> Int [conFreq] :: TermFreqs -> Int [litFreq] :: TermFreqs -> Int [sortFreq] :: TermFreqs -> Int [lamFreq] :: TermFreqs -> Int [piFreq] :: TermFreqs -> Int [funFreq] :: TermFreqs -> Int data ElimFreqs ElimFreqs :: Int -> Int -> ElimFreqs [applyFreq] :: ElimFreqs -> Int [projFreq] :: ElimFreqs -> Int data HiddenFreqs HiddenFreqs :: Int -> Int -> HiddenFreqs [hiddenFreq] :: HiddenFreqs -> Int [notHiddenFreq] :: HiddenFreqs -> Int data SortFreqs SortFreqs :: [Int] -> Int -> SortFreqs [setFreqs] :: SortFreqs -> [Int] [propFreq] :: SortFreqs -> Int defaultFrequencies :: Frequencies noProp :: TermConfiguration -> TermConfiguration data UseLiterals UseLit :: Bool -> Bool -> Bool -> Bool -> UseLiterals [useLitInt] :: UseLiterals -> Bool [useLitFloat] :: UseLiterals -> Bool [useLitString] :: UseLiterals -> Bool [useLitChar] :: UseLiterals -> Bool noLiterals :: UseLiterals fixSizeConf :: Int -> TermConfiguration -> TermConfiguration resizeConf :: (Int -> Int) -> TermConfiguration -> TermConfiguration decrConf :: TermConfiguration -> TermConfiguration divConf :: TermConfiguration -> Int -> TermConfiguration isTypeConf :: TermConfiguration -> TermConfiguration isntTypeConf :: TermConfiguration -> TermConfiguration extendConf :: TermConfiguration -> TermConfiguration extendWithTelConf :: Telescope -> TermConfiguration -> TermConfiguration makeConfiguration :: [RawName] -> [RawName] -> [RawName] -> [Nat] -> TermConfiguration class GenC a genC :: GenC a => TermConfiguration -> Gen a newtype YesType a YesType :: a -> YesType a [unYesType] :: YesType a -> a newtype NoType a NoType :: a -> NoType a [unNoType] :: NoType a -> a newtype VarName VarName :: Nat -> VarName [unVarName] :: VarName -> Nat newtype DefName DefName :: QName -> DefName [unDefName] :: DefName -> QName newtype ConName ConName :: ConHead -> ConName [unConName] :: ConName -> ConHead newtype ProjName ProjName :: QName -> ProjName [unProjName] :: ProjName -> QName newtype SizedList a SizedList :: [a] -> SizedList a [unSizedList] :: SizedList a -> [a] fixSize :: TermConfiguration -> Gen a -> Gen a genArgs :: TermConfiguration -> Gen Args genElims :: TermConfiguration -> Gen Elims -- | Only generates default configurations. Names and free variables -- varies. genConf :: Gen TermConfiguration class ShrinkC a b | a -> b shrinkC :: ShrinkC a b => TermConfiguration -> a -> [b] noShrink :: ShrinkC a b => a -> b killAbs :: KillVar a => Abs a -> a class KillVar a killVar :: KillVar a => Nat -> a -> a isWellScoped :: FreeVS a => TermConfiguration -> a -> Bool -- | Check that the generated terms don't have any out of scope variables. prop_wellScopedVars :: TermConfiguration -> Property instance GHC.Show.Show Agda.TypeChecking.Test.Generators.TermConfiguration instance GHC.Show.Show Agda.TypeChecking.Test.Generators.UseLiterals instance GHC.Show.Show Agda.TypeChecking.Test.Generators.Frequencies instance GHC.Show.Show Agda.TypeChecking.Test.Generators.SortFreqs instance GHC.Show.Show Agda.TypeChecking.Test.Generators.HiddenFreqs instance GHC.Show.Show Agda.TypeChecking.Test.Generators.ElimFreqs instance GHC.Show.Show Agda.TypeChecking.Test.Generators.TermFreqs instance Agda.TypeChecking.Test.Generators.GenC a => Agda.TypeChecking.Test.Generators.GenC (Agda.TypeChecking.Test.Generators.SizedList a) instance Agda.TypeChecking.Test.Generators.GenC a => Agda.TypeChecking.Test.Generators.GenC [a] instance (Agda.TypeChecking.Test.Generators.GenC a, Agda.TypeChecking.Test.Generators.GenC b) => Agda.TypeChecking.Test.Generators.GenC (a, b) instance Agda.TypeChecking.Test.Generators.GenC Agda.Syntax.Position.Range instance Agda.TypeChecking.Test.Generators.GenC Agda.Syntax.Common.Hiding instance (Agda.TypeChecking.Test.Generators.GenC c, Agda.TypeChecking.Test.Generators.GenC a) => Agda.TypeChecking.Test.Generators.GenC (Agda.Syntax.Common.Arg c a) instance (Agda.TypeChecking.Test.Generators.GenC c, Agda.TypeChecking.Test.Generators.GenC a) => Agda.TypeChecking.Test.Generators.GenC (Agda.Syntax.Common.Dom c a) instance Agda.TypeChecking.Test.Generators.GenC a => Agda.TypeChecking.Test.Generators.GenC (Agda.Syntax.Internal.Abs a) instance Agda.TypeChecking.Test.Generators.GenC a => Agda.TypeChecking.Test.Generators.GenC (Agda.Syntax.Internal.Elim' a) instance Agda.TypeChecking.Test.Generators.GenC Agda.TypeChecking.Test.Generators.DefName instance Agda.TypeChecking.Test.Generators.GenC Agda.TypeChecking.Test.Generators.ProjName instance Agda.TypeChecking.Test.Generators.GenC Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Test.Generators.GenC GHC.Types.Char instance Agda.TypeChecking.Test.Generators.GenC GHC.Types.Double instance Agda.TypeChecking.Test.Generators.GenC GHC.Integer.Type.Integer instance Agda.TypeChecking.Test.Generators.GenC Agda.Syntax.Literal.Literal instance Agda.TypeChecking.Test.Generators.GenC Agda.Syntax.Internal.Telescope instance Agda.TypeChecking.Test.Generators.GenC Agda.Syntax.Internal.Type instance Agda.TypeChecking.Test.Generators.GenC Agda.Syntax.Internal.Term instance Test.QuickCheck.Arbitrary.Arbitrary Agda.TypeChecking.Test.Generators.TermConfiguration instance Agda.TypeChecking.Test.Generators.ShrinkC a b => Agda.TypeChecking.Test.Generators.ShrinkC (Agda.TypeChecking.Test.Generators.YesType a) b instance Agda.TypeChecking.Test.Generators.ShrinkC a b => Agda.TypeChecking.Test.Generators.ShrinkC (Agda.TypeChecking.Test.Generators.NoType a) b instance Agda.TypeChecking.Test.Generators.ShrinkC a b => Agda.TypeChecking.Test.Generators.ShrinkC [a] [b] instance (Agda.TypeChecking.Test.Generators.ShrinkC a a', Agda.TypeChecking.Test.Generators.ShrinkC b b') => Agda.TypeChecking.Test.Generators.ShrinkC (a, b) (a', b') instance Agda.TypeChecking.Test.Generators.ShrinkC Agda.TypeChecking.Test.Generators.VarName Agda.Syntax.Common.Nat instance Agda.TypeChecking.Test.Generators.ShrinkC Agda.TypeChecking.Test.Generators.DefName Agda.Syntax.Abstract.Name.QName instance Agda.TypeChecking.Test.Generators.ShrinkC Agda.TypeChecking.Test.Generators.ConName Agda.Syntax.Internal.ConHead instance Agda.TypeChecking.Test.Generators.ShrinkC Agda.Syntax.Literal.Literal Agda.Syntax.Literal.Literal instance Agda.TypeChecking.Test.Generators.ShrinkC GHC.Types.Char GHC.Types.Char instance Agda.TypeChecking.Test.Generators.ShrinkC Agda.Syntax.Common.Hiding Agda.Syntax.Common.Hiding instance Agda.TypeChecking.Test.Generators.ShrinkC a b => Agda.TypeChecking.Test.Generators.ShrinkC (Agda.Syntax.Internal.Abs a) (Agda.Syntax.Internal.Abs b) instance Agda.TypeChecking.Test.Generators.ShrinkC a b => Agda.TypeChecking.Test.Generators.ShrinkC (Agda.Syntax.Internal.Arg a) (Agda.Syntax.Internal.Arg b) instance Agda.TypeChecking.Test.Generators.ShrinkC a b => Agda.TypeChecking.Test.Generators.ShrinkC (Agda.Syntax.Internal.Dom a) (Agda.Syntax.Internal.Dom b) instance Agda.TypeChecking.Test.Generators.ShrinkC a b => Agda.TypeChecking.Test.Generators.ShrinkC (Agda.Syntax.Internal.Blocked a) (Agda.Syntax.Internal.Blocked b) instance Agda.TypeChecking.Test.Generators.ShrinkC a b => Agda.TypeChecking.Test.Generators.ShrinkC (Agda.Syntax.Internal.Elim' a) (Agda.Syntax.Internal.Elim' b) instance Agda.TypeChecking.Test.Generators.ShrinkC Agda.Syntax.Internal.Sort Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Test.Generators.ShrinkC Agda.Syntax.Internal.Telescope Agda.Syntax.Internal.Telescope instance Agda.TypeChecking.Test.Generators.ShrinkC Agda.Syntax.Internal.Type Agda.Syntax.Internal.Type instance Agda.TypeChecking.Test.Generators.ShrinkC Agda.Syntax.Internal.Term Agda.Syntax.Internal.Term instance Agda.TypeChecking.Test.Generators.KillVar Agda.Syntax.Internal.Term instance Agda.TypeChecking.Test.Generators.KillVar Agda.Syntax.Internal.Type instance Agda.TypeChecking.Test.Generators.KillVar Agda.Syntax.Internal.Telescope instance Agda.TypeChecking.Test.Generators.KillVar a => Agda.TypeChecking.Test.Generators.KillVar (Agda.Syntax.Internal.Elim' a) instance Agda.TypeChecking.Test.Generators.KillVar a => Agda.TypeChecking.Test.Generators.KillVar (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.Test.Generators.KillVar a => Agda.TypeChecking.Test.Generators.KillVar (Agda.Syntax.Internal.Dom a) instance Agda.TypeChecking.Test.Generators.KillVar a => Agda.TypeChecking.Test.Generators.KillVar (Agda.Syntax.Internal.Abs a) instance Agda.TypeChecking.Test.Generators.KillVar a => Agda.TypeChecking.Test.Generators.KillVar [a] instance Agda.TypeChecking.Test.Generators.KillVar a => Agda.TypeChecking.Test.Generators.KillVar (GHC.Base.Maybe a) instance (Agda.TypeChecking.Test.Generators.KillVar a, Agda.TypeChecking.Test.Generators.KillVar b) => Agda.TypeChecking.Test.Generators.KillVar (a, b) -- | Tests for free variable computations. module Agda.TypeChecking.Free.Tests -- | All tests as collected by quickCheckAll. tests :: IO Bool module Agda.TypeChecking.Monad.Builtin class (Functor m, Applicative m, Monad m) => HasBuiltins m getBuiltinThing :: HasBuiltins m => String -> m (Maybe (Builtin PrimFun)) litType :: Literal -> TCM Type setBuiltinThings :: BuiltinThings PrimFun -> TCM () bindBuiltinName :: String -> Term -> TCM () bindPrimitive :: String -> PrimFun -> TCM () getBuiltin :: String -> TCM Term getBuiltin' :: HasBuiltins m => String -> m (Maybe Term) getPrimitive' :: HasBuiltins m => String -> m (Maybe PrimFun) getPrimitive :: String -> TCM PrimFun -- | Rewrite a literal to constructor form if possible. constructorForm :: Term -> TCM Term constructorForm' :: Applicative m => m Term -> m Term -> Term -> m Term primInteger :: TCM Term primFloat :: TCM Term primChar :: TCM Term primString :: TCM Term primBool :: TCM Term primTrue :: TCM Term primFalse :: TCM Term primList :: TCM Term primNil :: TCM Term primCons :: TCM Term primIO :: TCM Term primNat :: TCM Term primSuc :: TCM Term primZero :: TCM Term primNatPlus :: TCM Term primNatMinus :: TCM Term primNatTimes :: TCM Term primNatDivSucAux :: TCM Term primNatModSucAux :: TCM Term primNatEquality :: TCM Term primNatLess :: TCM Term primSizeUniv :: TCM Term primSize :: TCM Term primSizeLt :: TCM Term primSizeSuc :: TCM Term primSizeInf :: TCM Term primSizeMax :: TCM Term primInf :: TCM Term primSharp :: TCM Term primFlat :: TCM Term primEquality :: TCM Term primRefl :: TCM Term primRewrite :: TCM Term primLevel :: TCM Term primLevelZero :: TCM Term primLevelSuc :: TCM Term primLevelMax :: TCM Term primIrrAxiom :: TCM Term primQName :: TCM Term primArgInfo :: TCM Term primArgArgInfo :: TCM Term primArg :: TCM Term primArgArg :: TCM Term primAgdaTerm :: TCM Term primAgdaTermVar :: TCM Term primAgdaTermLam :: TCM Term primAgdaTermExtLam :: TCM Term primAgdaTermDef :: TCM Term primAgdaTermCon :: TCM Term primAgdaTermPi :: TCM Term primAgdaTermSort :: TCM Term primAgdaTermLit :: TCM Term primAgdaTermUnsupported :: TCM Term primAgdaType :: TCM Term primAgdaTypeEl :: TCM Term primHiding :: TCM Term primHidden :: TCM Term primInstance :: TCM Term primVisible :: TCM Term primRelevance :: TCM Term primRelevant :: TCM Term primIrrelevant :: TCM Term primAgdaLiteral :: TCM Term primAgdaLitNat :: TCM Term primAgdaLitFloat :: TCM Term primAgdaLitString :: TCM Term primAgdaLitChar :: TCM Term primAgdaLitQName :: TCM Term primAgdaSort :: TCM Term primAgdaSortSet :: TCM Term primAgdaSortLit :: TCM Term primAgdaSortUnsupported :: TCM Term primAgdaDefinition :: TCM Term primAgdaDefinitionFunDef :: TCM Term primAgdaDefinitionDataDef :: TCM Term primAgdaDefinitionRecordDef :: TCM Term primAgdaDefinitionPostulate :: TCM Term primAgdaDefinitionPrimitive :: TCM Term primAgdaDefinitionDataConstructor :: TCM Term primAgdaFunDef :: TCM Term primAgdaFunDefCon :: TCM Term primAgdaClause :: TCM Term primAgdaClauseClause :: TCM Term primAgdaClauseAbsurd :: TCM Term primAgdaPattern :: TCM Term primAgdaPatCon :: TCM Term primAgdaPatVar :: TCM Term primAgdaPatDot :: TCM Term primAgdaDataDef :: TCM Term primAgdaRecordDef :: TCM Term primAgdaPatLit :: TCM Term primAgdaPatProj :: TCM Term primAgdaPatAbsurd :: TCM Term builtinNat :: String builtinSuc :: String builtinZero :: String builtinNatPlus :: String builtinNatMinus :: String builtinNatTimes :: String builtinNatDivSucAux :: String builtinNatModSucAux :: String builtinNatEquals :: String builtinNatLess :: String builtinInteger :: String builtinFloat :: String builtinChar :: String builtinString :: String builtinBool :: String builtinTrue :: String builtinFalse :: String builtinList :: String builtinNil :: String builtinCons :: String builtinIO :: String builtinSizeUniv :: String builtinSize :: String builtinSizeLt :: String builtinSizeSuc :: String builtinSizeInf :: String builtinSizeMax :: String builtinInf :: String builtinSharp :: String builtinFlat :: String builtinEquality :: String builtinRefl :: String builtinRewrite :: String builtinLevelMax :: String builtinLevel :: String builtinLevelZero :: String builtinLevelSuc :: String builtinIrrAxiom :: String builtinQName :: String builtinAgdaSort :: String builtinAgdaSortSet :: String builtinAgdaSortLit :: String builtinAgdaSortUnsupported :: String builtinAgdaType :: String builtinAgdaTypeEl :: String builtinHiding :: String builtinHidden :: String builtinInstance :: String builtinVisible :: String builtinRelevance :: String builtinRelevant :: String builtinIrrelevant :: String builtinArg :: String builtinArgInfo :: String builtinArgArgInfo :: String builtinArgArg :: String builtinAgdaTerm :: String builtinAgdaTermVar :: String builtinAgdaTermLam :: String builtinAgdaTermExtLam :: String builtinAgdaTermDef :: String builtinAgdaTermCon :: String builtinAgdaTermPi :: String builtinAgdaTermSort :: String builtinAgdaTermLit :: String builtinAgdaTermUnsupported :: String builtinAgdaLiteral :: String builtinAgdaLitNat :: String builtinAgdaLitFloat :: String builtinAgdaLitChar :: String builtinAgdaLitString :: String builtinAgdaLitQName :: String builtinAgdaFunDef :: String builtinAgdaFunDefCon :: String builtinAgdaClause :: String builtinAgdaClauseClause :: String builtinAgdaClauseAbsurd :: String builtinAgdaPattern :: String builtinAgdaPatVar :: String builtinAgdaPatCon :: String builtinAgdaPatDot :: String builtinAgdaPatLit :: String builtinAgdaPatProj :: String builtinAgdaPatAbsurd :: String builtinAgdaDataDef :: String builtinAgdaRecordDef :: String builtinAgdaDefinitionFunDef :: String builtinAgdaDefinitionDataDef :: String builtinAgdaDefinitionRecordDef :: String builtinAgdaDefinitionDataConstructor :: String builtinAgdaDefinitionPostulate :: String builtinAgdaDefinitionPrimitive :: String builtinAgdaDefinition :: String -- | Builtins that come without a definition in Agda syntax. These are -- giving names to Agda internal concepts which cannot be assigned an -- Agda type. -- -- An example would be a user-defined name for Set. -- -- {--} -- -- The type of Type would be Type : Level → Setω which -- is not valid Agda. builtinsNoDef :: [String] -- | The coinductive primitives. data CoinductionKit CoinductionKit :: QName -> QName -> QName -> CoinductionKit [nameOfInf] :: CoinductionKit -> QName [nameOfSharp] :: CoinductionKit -> QName [nameOfFlat] :: CoinductionKit -> QName -- | Tries to build a CoinductionKit. coinductionKit' :: TCM CoinductionKit coinductionKit :: TCM (Maybe CoinductionKit) -- | Get the name of the equality type. primEqualityName :: TCM QName instance Control.Monad.IO.Class.MonadIO m => Agda.TypeChecking.Monad.Builtin.HasBuiltins (Agda.TypeChecking.Monad.Base.TCMT m) -- | Lenses for TCState and more. module Agda.TypeChecking.Monad.State -- | Resets the non-persistent part of the type checking state. resetState :: TCM () -- | Resets all of the type checking state. -- -- Keep only Benchmark information. resetAllState :: TCM () -- | Restore TCState after performing subcomputation. -- -- In contrast to localState, the Benchmark info from the -- subcomputation is saved. localTCState :: TCM a -> TCM a -- | Same as localTCState but also returns the state in which we -- were just before reverting it. localTCStateSaving :: TCM a -> TCM (a, TCState) lensPersistentState :: Lens' PersistentTCState TCState updatePersistentState :: (PersistentTCState -> PersistentTCState) -> (TCState -> TCState) modifyPersistentState :: (PersistentTCState -> PersistentTCState) -> TCM () -- | Lens for stAccumStatistics. lensAccumStatisticsP :: Lens' Statistics PersistentTCState lensAccumStatistics :: Lens' Statistics TCState -- | Get the current scope. getScope :: TCM ScopeInfo -- | Set the current scope. setScope :: ScopeInfo -> TCM () -- | Modify the current scope. modifyScope :: (ScopeInfo -> ScopeInfo) -> TCM () -- | Run a computation in a local scope. withScope :: ScopeInfo -> TCM a -> TCM (a, ScopeInfo) -- | Same as withScope, but discard the scope from the computation. withScope_ :: ScopeInfo -> TCM a -> TCM a -- | Discard any changes to the scope by a computation. localScope :: TCM a -> TCM a -- | Scope error. notInScope :: QName -> TCM a -- | Debug print the scope. printScope :: String -> Int -> String -> TCM () modifySignature :: (Signature -> Signature) -> TCM () modifyImportedSignature :: (Signature -> Signature) -> TCM () getSignature :: TCM Signature getImportedSignature :: TCM Signature setSignature :: Signature -> TCM () setImportedSignature :: Signature -> TCM () -- | Run some computation in a different signature, restore original -- signature. withSignature :: Signature -> TCM a -> TCM a addRewriteRulesFor :: QName -> RewriteRules -> Signature -> Signature lookupDefinition :: QName -> Signature -> Maybe Definition updateDefinitions :: (Definitions -> Definitions) -> Signature -> Signature updateDefinition :: QName -> (Definition -> Definition) -> Signature -> Signature updateTheDef :: (Defn -> Defn) -> (Definition -> Definition) updateDefType :: (Type -> Type) -> (Definition -> Definition) updateDefArgOccurrences :: ([Occurrence] -> [Occurrence]) -> (Definition -> Definition) updateDefPolarity :: ([Polarity] -> [Polarity]) -> (Definition -> Definition) updateDefCompiledRep :: (CompiledRepresentation -> CompiledRepresentation) -> (Definition -> Definition) updateFunClauses :: ([Clause] -> [Clause]) -> (Defn -> Defn) -- | Set the top-level module. This affects the global module id of freshly -- generated names. setTopLevelModule :: QName -> TCM () -- | Use a different top-level module for a computation. Used when -- generating names for imported modules. withTopLevelModule :: QName -> TCM a -> TCM a -- | Tell the compiler to import the given Haskell module. addHaskellImport :: String -> TCM () -- | Get the Haskell imports. getHaskellImports :: TCM (Set String) getInteractionOutputCallback :: TCM InteractionOutputCallback appInteractionOutputCallback :: Response -> TCM () setInteractionOutputCallback :: InteractionOutputCallback -> TCM () getPatternSyns :: TCM PatternSynDefns setPatternSyns :: PatternSynDefns -> TCM () -- | Lens for stPatternSyns. modifyPatternSyns :: (PatternSynDefns -> PatternSynDefns) -> TCM () getPatternSynImports :: TCM PatternSynDefns lookupPatternSyn :: QName -> TCM PatternSynDefn -- | Lens getter for Benchmark from TCState. theBenchmark :: TCState -> Benchmark -- | Lens map for Benchmark. updateBenchmark :: (Benchmark -> Benchmark) -> TCState -> TCState -- | Lens getter for Benchmark from TCM. getBenchmark :: TCM Benchmark -- | Lens modify for Benchmark. modifyBenchmark :: (Benchmark -> Benchmark) -> TCM () -- | Run a fresh instance of the TCM (with initial state). Benchmark -- info is preserved. freshTCM :: TCM a -> TCM (Either TCErr a) -- | Look through the signature and reconstruct the instance table. addSignatureInstances :: Signature -> TCM () -- | Lens for stInstanceDefs. updateInstanceDefs :: (TempInstanceTable -> TempInstanceTable) -> (TCState -> TCState) modifyInstanceDefs :: (TempInstanceTable -> TempInstanceTable) -> TCM () getAllInstanceDefs :: TCM TempInstanceTable getAnonInstanceDefs :: TCM [QName] -- | Remove all instances whose type is still unresolved. clearAnonInstanceDefs :: TCM () -- | Add an instance whose type is still unresolved. addUnknownInstance :: QName -> TCM () -- | Add instance to some `class'. addNamedInstance :: QName -> QName -> TCM () -- | Measure CPU time for individual phases of the Agda pipeline. module Agda.TypeChecking.Monad.Benchmark -- | Monad with access to benchmarking data. class (Ord a, Functor m, MonadIO m) => MonadBench a m | m -> a where getsBenchmark f = f <$> getBenchmark putBenchmark b = modifyBenchmark $ const b modifyBenchmark f = do { b <- getBenchmark; putBenchmark $! f b } getBenchmark :: MonadBench a m => m (Benchmark a) -- | When verbosity is set or changes, we need to turn benchmarking on or -- off. updateBenchmarkingStatus :: TCM () -- | Bill a computation to a specific account. Works even if the -- computation is aborted by an exception. billTo :: MonadBench a m => Account a -> m c -> m c -- | Bill a pure computation to a specific account. billPureTo :: MonadBench a m => Account a -> c -> m c -- | Prints the accumulated benchmark results. Does nothing if profiling is -- not activated at level 7. print :: MonadTCM tcm => tcm () -- | Functions which map between module names and file names. -- -- Note that file name lookups are cached in the TCState. The code -- assumes that no Agda source files are added or removed from the -- include directories while the code is being type checked. module Agda.Interaction.FindFile -- | Converts an Agda file name to the corresponding interface file name. toIFile :: AbsolutePath -> AbsolutePath -- | Errors which can arise when trying to find a source file. -- -- Invariant: All paths are absolute. data FindError -- | The file was not found. It should have had one of the given file -- names. NotFound :: [AbsolutePath] -> FindError -- | Several matching files were found. -- -- Invariant: The list of matching files has at least two elements. Ambiguous :: [AbsolutePath] -> FindError -- | Given the module name which the error applies to this function -- converts a FindError to a TypeError. findErrorToTypeError :: TopLevelModuleName -> FindError -> TypeError -- | Finds the source file corresponding to a given top-level module name. -- The returned paths are absolute. -- -- Raises an error if the file cannot be found. findFile :: TopLevelModuleName -> TCM AbsolutePath -- | Tries to find the source file corresponding to a given top-level -- module name. The returned paths are absolute. -- -- SIDE EFFECT: Updates stModuleToSource. findFile' :: TopLevelModuleName -> TCM (Either FindError AbsolutePath) -- | A variant of findFile' which does not require TCM. findFile'' :: [AbsolutePath] -> TopLevelModuleName -> ModuleToSource -> IO (Either FindError AbsolutePath, ModuleToSource) -- | Finds the interface file corresponding to a given top-level module -- name. The returned paths are absolute. -- -- Raises an error if the source file cannot be found, and returns -- Nothing if the source file can be found but not the interface -- file. findInterfaceFile :: TopLevelModuleName -> TCM (Maybe AbsolutePath) -- | Ensures that the module name matches the file name. The file -- corresponding to the module name (according to the include path) has -- to be the same as the given file name. checkModuleName :: TopLevelModuleName -> AbsolutePath -> TCM () -- | Computes the module name of the top-level module in the given file. -- -- Warning! Parses the whole file to get the module name out. Use wisely! moduleName' :: AbsolutePath -> TCM TopLevelModuleName -- | A variant of moduleName' which raises an error if the file name -- does not match the module name. -- -- The file name is interpreted relative to the current working directory -- (unless it is absolute). moduleName :: AbsolutePath -> TCM TopLevelModuleName tests :: IO Bool -- | Lenses for CommandLineOptions and PragmaOptions. -- -- Add as needed. -- -- Nothing smart happening here. module Agda.Interaction.Options.Lenses class LensPragmaOptions a where setPragmaOptions = mapPragmaOptions . const mapPragmaOptions f a = setPragmaOptions (f $ getPragmaOptions a) a getPragmaOptions :: LensPragmaOptions a => a -> PragmaOptions setPragmaOptions :: LensPragmaOptions a => PragmaOptions -> a -> a mapPragmaOptions :: LensPragmaOptions a => (PragmaOptions -> PragmaOptions) -> a -> a modifyPragmaOptions :: (PragmaOptions -> PragmaOptions) -> TCM () class LensVerbosity a where setVerbosity = mapVerbosity . const mapVerbosity f a = setVerbosity (f $ getVerbosity a) a getVerbosity :: LensVerbosity a => a -> Verbosity setVerbosity :: LensVerbosity a => Verbosity -> a -> a mapVerbosity :: LensVerbosity a => (Verbosity -> Verbosity) -> a -> a modifyVerbosity :: (Verbosity -> Verbosity) -> TCM () putVerbosity :: Verbosity -> TCM () class LensCommandLineOptions a where setCommandLineOptions = mapCommandLineOptions . const mapCommandLineOptions f a = setCommandLineOptions (f $ getCommandLineOptions a) a getCommandLineOptions :: LensCommandLineOptions a => a -> CommandLineOptions setCommandLineOptions :: LensCommandLineOptions a => CommandLineOptions -> a -> a mapCommandLineOptions :: LensCommandLineOptions a => (CommandLineOptions -> CommandLineOptions) -> a -> a modifyCommandLineOptions :: (CommandLineOptions -> CommandLineOptions) -> TCM () type SafeMode = Bool class LensSafeMode a where setSafeMode = mapSafeMode . const mapSafeMode f a = setSafeMode (f $ getSafeMode a) a getSafeMode :: LensSafeMode a => a -> SafeMode setSafeMode :: LensSafeMode a => SafeMode -> a -> a mapSafeMode :: LensSafeMode a => (SafeMode -> SafeMode) -> a -> a modifySafeMode :: (SafeMode -> SafeMode) -> TCM () putSafeMode :: SafeMode -> TCM () class LensIncludeDirs a where setIncludeDirs = mapIncludeDirs . const mapIncludeDirs f a = setIncludeDirs (f $ getIncludeDirs a) a getIncludeDirs :: LensIncludeDirs a => a -> IncludeDirs setIncludeDirs :: LensIncludeDirs a => IncludeDirs -> a -> a mapIncludeDirs :: LensIncludeDirs a => (IncludeDirs -> IncludeDirs) -> a -> a modifyIncludeDirs :: (IncludeDirs -> IncludeDirs) -> TCM () putIncludeDirs :: IncludeDirs -> TCM () type PersistentVerbosity = Verbosity class LensPersistentVerbosity a where setPersistentVerbosity = mapPersistentVerbosity . const mapPersistentVerbosity f a = setPersistentVerbosity (f $ getPersistentVerbosity a) a getPersistentVerbosity :: LensPersistentVerbosity a => a -> PersistentVerbosity setPersistentVerbosity :: LensPersistentVerbosity a => PersistentVerbosity -> a -> a mapPersistentVerbosity :: LensPersistentVerbosity a => (PersistentVerbosity -> PersistentVerbosity) -> a -> a modifyPersistentVerbosity :: (PersistentVerbosity -> PersistentVerbosity) -> TCM () putPersistentVerbosity :: PersistentVerbosity -> TCM () instance Agda.Interaction.Options.Lenses.LensPragmaOptions Agda.Interaction.Options.CommandLineOptions instance Agda.Interaction.Options.Lenses.LensPragmaOptions Agda.TypeChecking.Monad.Base.TCState instance Agda.Interaction.Options.Lenses.LensVerbosity Agda.Interaction.Options.PragmaOptions instance Agda.Interaction.Options.Lenses.LensVerbosity Agda.TypeChecking.Monad.Base.TCState instance Agda.Interaction.Options.Lenses.LensCommandLineOptions Agda.TypeChecking.Monad.Base.PersistentTCState instance Agda.Interaction.Options.Lenses.LensCommandLineOptions Agda.TypeChecking.Monad.Base.TCState instance Agda.Interaction.Options.Lenses.LensSafeMode Agda.Interaction.Options.CommandLineOptions instance Agda.Interaction.Options.Lenses.LensSafeMode Agda.TypeChecking.Monad.Base.PersistentTCState instance Agda.Interaction.Options.Lenses.LensSafeMode Agda.TypeChecking.Monad.Base.TCState instance Agda.Interaction.Options.Lenses.LensIncludeDirs Agda.Interaction.Options.CommandLineOptions instance Agda.Interaction.Options.Lenses.LensIncludeDirs Agda.TypeChecking.Monad.Base.PersistentTCState instance Agda.Interaction.Options.Lenses.LensIncludeDirs Agda.TypeChecking.Monad.Base.TCState instance Agda.Interaction.Options.Lenses.LensPersistentVerbosity Agda.Interaction.Options.PragmaOptions instance Agda.Interaction.Options.Lenses.LensPersistentVerbosity Agda.Interaction.Options.CommandLineOptions instance Agda.Interaction.Options.Lenses.LensPersistentVerbosity Agda.TypeChecking.Monad.Base.PersistentTCState instance Agda.Interaction.Options.Lenses.LensPersistentVerbosity Agda.TypeChecking.Monad.Base.TCState module Agda.TypeChecking.Monad.Options -- | Sets the pragma options. setPragmaOptions :: PragmaOptions -> TCM () -- | Sets the command line options (both persistent and pragma options are -- updated). -- -- Relative include directories are made absolute with respect to the -- current working directory. If the include directories have changed -- (thus, they are Left now, and were previously Right -- something), then the state is reset (completely, see -- setIncludeDirs) . -- -- An empty list of relative include directories (Left -- []) is interpreted as ["."]. setCommandLineOptions :: CommandLineOptions -> TCM () class (Functor m, Applicative m, Monad m) => HasOptions m -- | Returns the pragma options which are currently in effect. pragmaOptions :: HasOptions m => m PragmaOptions -- | Returns the command line options which are currently in effect. commandLineOptions :: HasOptions m => m CommandLineOptions setOptionsFromPragma :: OptionsPragma -> TCM () -- | Disable display forms. enableDisplayForms :: TCM a -> TCM a -- | Disable display forms. disableDisplayForms :: TCM a -> TCM a -- | Check if display forms are enabled. displayFormsEnabled :: TCM Bool -- | Don't eta contract implicit dontEtaContractImplicit :: TCM a -> TCM a -- | Do eta contract implicit doEtaContractImplicit :: MonadTCM tcm => tcm a -> tcm a shouldEtaContractImplicit :: MonadReader TCEnv m => m Bool -- | Don't reify interaction points dontReifyInteractionPoints :: TCM a -> TCM a shouldReifyInteractionPoints :: TCM Bool -- | Gets the include directories. -- -- Precondition: optIncludeDirs must be Right -- something. getIncludeDirs :: TCM [AbsolutePath] -- | Which directory should form the base of relative include paths? data RelativeTo -- | The root directory of the "project" containing the given file. The -- file needs to be syntactically correct, with a module name matching -- the file name. ProjectRoot :: AbsolutePath -> RelativeTo -- | The current working directory. CurrentDir :: RelativeTo -- | Makes the given directories absolute and stores them as include -- directories. -- -- If the include directories change (and they were previously -- Right something), then the state is reset (completely, -- except for the include directories and -- stInteractionOutputCallback). -- -- An empty list is interpreted as ["."]. setIncludeDirs :: [FilePath] -> RelativeTo -> TCM () setInputFile :: FilePath -> TCM () -- | Should only be run if hasInputFile. getInputFile :: TCM AbsolutePath -- | Return the optInputFile as AbsolutePath, if any. getInputFile' :: TCM (Maybe AbsolutePath) hasInputFile :: TCM Bool proofIrrelevance :: TCM Bool hasUniversePolymorphism :: HasOptions m => m Bool showImplicitArguments :: TCM Bool showIrrelevantArguments :: TCM Bool -- | Switch on printing of implicit and irrelevant arguments. E.g. for -- reification in with-function generation. withShowAllArguments :: TCM a -> TCM a ignoreInterfaces :: TCM Bool positivityCheckEnabled :: TCM Bool typeInType :: TCM Bool -- | Retrieve the current verbosity level. getVerbosity :: HasOptions m => m (Trie String Int) type VerboseKey = String -- | Check whether a certain verbosity level is activated. -- -- Precondition: The level must be non-negative. hasVerbosity :: HasOptions m => VerboseKey -> Int -> m Bool -- | Displays a debug message in a suitable way. displayDebugMessage :: MonadTCM tcm => Int -> String -> tcm () -- | Run a computation if a certain verbosity level is activated. -- -- Precondition: The level must be non-negative. verboseS :: MonadTCM tcm => VerboseKey -> Int -> tcm () -> tcm () -- | Conditionally print debug string. reportS :: MonadTCM tcm => VerboseKey -> Int -> String -> tcm () -- | Conditionally println debug string. reportSLn :: MonadTCM tcm => VerboseKey -> Int -> String -> tcm () -- | Conditionally render debug Doc and print it. reportSDoc :: MonadTCM tcm => VerboseKey -> Int -> TCM Doc -> tcm () -- | Print brackets around debug messages issued by a computation. verboseBracket :: MonadTCM tcm => VerboseKey -> Int -> String -> TCM a -> tcm a instance Control.Monad.IO.Class.MonadIO m => Agda.TypeChecking.Monad.Options.HasOptions (Agda.TypeChecking.Monad.Base.TCMT m) -- | The translation of abstract syntax to concrete syntax has two -- purposes. First it allows us to pretty print abstract syntax values -- without having to write a dedicated pretty printer, and second it -- serves as a sanity check for the concrete to abstract translation: -- translating from concrete to abstract and then back again should be -- (more or less) the identity. module Agda.Syntax.Translation.AbstractToConcrete class ToConcrete a c | a -> c where toConcrete x = bindToConcrete x return bindToConcrete x ret = ret =<< toConcrete x toConcrete :: ToConcrete a c => a -> AbsToCon c bindToConcrete :: ToConcrete a c => a -> (c -> AbsToCon b) -> AbsToCon b -- | Translate something in a context of the given precedence. toConcreteCtx :: ToConcrete a c => Precedence -> a -> AbsToCon c abstractToConcrete_ :: ToConcrete a c => a -> TCM c abstractToConcreteEnv :: ToConcrete a c => Env -> a -> TCM c runAbsToCon :: AbsToCon c -> TCM c data RangeAndPragma RangeAndPragma :: Range -> Pragma -> RangeAndPragma abstractToConcreteCtx :: ToConcrete a c => Precedence -> a -> TCM c withScope :: ScopeInfo -> AbsToCon a -> AbsToCon a makeEnv :: ScopeInfo -> Env -- | We put the translation into TCM in order to print debug messages. type AbsToCon = ReaderT Env TCM data DontTouchMe a data Env noTakenNames :: AbsToCon a -> AbsToCon a instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a c => Agda.Syntax.Translation.AbstractToConcrete.ToConcrete [a] [c] instance (Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a1 c1, Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a2 c2) => Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (a1, a2) (c1, c2) instance (Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a1 c1, Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a2 c2, Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a3 c3) => Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (a1, a2, a3) (c1, c2, c3) instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (Agda.Syntax.Common.ArgInfo ac) Agda.Syntax.Concrete.ArgInfo instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a c => Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (Agda.Syntax.Common.Arg ac a) (Agda.Syntax.Concrete.Arg c) instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a c => Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (Agda.Syntax.Common.WithHiding a) (Agda.Syntax.Common.WithHiding c) instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a c => Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (Agda.Syntax.Common.Named name a) (Agda.Syntax.Common.Named name c) instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (Agda.Syntax.Translation.AbstractToConcrete.DontTouchMe a) a instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.Name.Name Agda.Syntax.Concrete.Name.Name instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.Name.QName Agda.Syntax.Concrete.Name.QName instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.Name.ModuleName Agda.Syntax.Concrete.Name.QName instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.Expr Agda.Syntax.Concrete.Expr instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.LamBinding [Agda.Syntax.Concrete.LamBinding] instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.TypedBindings [Agda.Syntax.Concrete.TypedBindings] instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.TypedBinding Agda.Syntax.Concrete.TypedBinding instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.LetBinding [Agda.Syntax.Concrete.Declaration] instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Translation.AbstractToConcrete.AsWhereDecls Agda.Syntax.Concrete.WhereClause instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.RHS (Agda.Syntax.Concrete.RHS, [Agda.Syntax.Concrete.Expr], [Agda.Syntax.Concrete.Expr], [Agda.Syntax.Concrete.Declaration]) instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (GHC.Base.Maybe Agda.Syntax.Abstract.Name.QName) (GHC.Base.Maybe Agda.Syntax.Concrete.Name.Name) instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (Agda.Syntax.Common.Constr Agda.Syntax.Abstract.Constructor) Agda.Syntax.Concrete.Declaration instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a Agda.Syntax.Concrete.LHS => Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (Agda.Syntax.Abstract.Clause' a) [Agda.Syntax.Concrete.Declaration] instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.ModuleApplication Agda.Syntax.Concrete.ModuleApplication instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.Declaration [Agda.Syntax.Concrete.Declaration] instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Translation.AbstractToConcrete.RangeAndPragma Agda.Syntax.Concrete.Pragma instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.SpineLHS Agda.Syntax.Concrete.LHS instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.LHS Agda.Syntax.Concrete.LHS instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.LHSCore Agda.Syntax.Concrete.Pattern instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Abstract.Pattern Agda.Syntax.Concrete.Pattern instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.Syntax.Common.InteractionId Agda.Syntax.Concrete.Expr instance Agda.Syntax.Translation.AbstractToConcrete.ToConcrete Agda.TypeChecking.Monad.Base.NamedMeta Agda.Syntax.Concrete.Expr -- | The scope monad with operations. module Agda.Syntax.Scope.Monad -- | To simplify interaction between scope checking and type checking (in -- particular when chasing imports), we use the same monad. type ScopeM = TCM isDatatypeModule :: ModuleName -> ScopeM Bool getCurrentModule :: ScopeM ModuleName setCurrentModule :: ModuleName -> ScopeM () withCurrentModule :: ModuleName -> ScopeM a -> ScopeM a withCurrentModule' :: (MonadTrans t, Monad (t ScopeM)) => ModuleName -> t ScopeM a -> t ScopeM a getNamedScope :: ModuleName -> ScopeM Scope getCurrentScope :: ScopeM Scope -- | Create a new module with an empty scope (Bool is True if it is a -- datatype module) createModule :: Bool -> ModuleName -> ScopeM () -- | Apply a function to the scope info. modifyScopeInfo :: (ScopeInfo -> ScopeInfo) -> ScopeM () -- | Apply a function to the scope map. modifyScopes :: (Map ModuleName Scope -> Map ModuleName Scope) -> ScopeM () -- | Apply a function to the given scope. modifyNamedScope :: ModuleName -> (Scope -> Scope) -> ScopeM () setNamedScope :: ModuleName -> Scope -> ScopeM () -- | Apply a monadic function to the top scope. modifyNamedScopeM :: ModuleName -> (Scope -> ScopeM Scope) -> ScopeM () -- | Apply a function to the current scope. modifyCurrentScope :: (Scope -> Scope) -> ScopeM () modifyCurrentScopeM :: (Scope -> ScopeM Scope) -> ScopeM () -- | Apply a function to the public or private name space. modifyCurrentNameSpace :: NameSpaceId -> (NameSpace -> NameSpace) -> ScopeM () setContextPrecedence :: Precedence -> ScopeM () getContextPrecedence :: ScopeM Precedence withContextPrecedence :: Precedence -> ScopeM a -> ScopeM a getLocalVars :: ScopeM LocalVars modifyLocalVars :: (LocalVars -> LocalVars) -> ScopeM () setLocalVars :: LocalVars -> ScopeM () -- | Run a computation without changing the local variables. withLocalVars :: ScopeM a -> ScopeM a -- | Create a fresh abstract name from a concrete name. -- -- This function is used when we translate a concrete name in a binder. -- The Range of the concrete name is saved as the -- nameBindingSite of the abstract name. freshAbstractName :: Fixity' -> Name -> ScopeM Name -- |
--   freshAbstractName_ = freshAbstractName defaultFixity
--   
freshAbstractName_ :: Name -> ScopeM Name -- | Create a fresh abstract qualified name. freshAbstractQName :: Fixity' -> Name -> ScopeM QName data ResolvedName VarName :: Name -> ResolvedName DefinedName :: Access -> AbstractName -> ResolvedName -- | record fields names need to be distinguished to parse copatterns FieldName :: AbstractName -> ResolvedName ConstructorName :: [AbstractName] -> ResolvedName PatternSynResName :: AbstractName -> ResolvedName UnknownName :: ResolvedName -- | Look up the abstract name referred to by a given concrete name. resolveName :: QName -> ScopeM ResolvedName -- | Look up the abstract name corresponding to a concrete name of a -- certain kind and/or from a given set of names. Sometimes we know -- already that we are dealing with a constructor or pattern synonym -- (e.g. when we have parsed a pattern). Then, we can ignore conflicting -- definitions of that name of a different kind. (See issue 822.) resolveName' :: [KindOfName] -> Maybe (Set Name) -> QName -> ScopeM ResolvedName -- | Look up a module in the scope. resolveModule :: QName -> ScopeM AbstractModule -- | Get the notation of a name. The name is assumed to be in scope. getNotation :: QName -> Set Name -> ScopeM NewNotation -- | Bind a variable. The abstract name is supplied as the second argument. bindVariable :: Name -> Name -> ScopeM () -- | Bind a defined name. Must not shadow anything. bindName :: Access -> KindOfName -> Name -> QName -> ScopeM () -- | Rebind a name. Use with care! Ulf, 2014-06-29: Currently used to -- rebind the name defined by an unquoteDecl, which is a -- QuotableName in the body, but a DefinedName later on. rebindName :: Access -> KindOfName -> Name -> QName -> ScopeM () -- | Bind a module name. bindModule :: Access -> Name -> ModuleName -> ScopeM () -- | Bind a qualified module name. Adds it to the imports field of the -- scope. bindQModule :: Access -> QName -> ModuleName -> ScopeM () -- | Clear the scope of any no names. stripNoNames :: ScopeM () type Out = (Ren ModuleName, Ren QName) type WSM = StateT Out ScopeM -- | Create a new scope with the given name from an old scope. Renames -- public names in the old scope to match the new name and returns the -- renamings. -- -- Data and record types share a common abstract name with their module. -- This invariant needs to be preserved by copyScope, since -- constructors (fields) can be qualified by their data (record) type -- name (as an alternative to qualification by their module). (See Issue -- 836). copyScope :: QName -> ModuleName -> Scope -> ScopeM (Scope, (Ren ModuleName, Ren QName)) -- | Apply an import directive and check that all the names mentioned -- actually exist. applyImportDirectiveM :: QName -> ImportDirective -> Scope -> ScopeM Scope -- | Open a module. openModule_ :: QName -> ImportDirective -> ScopeM () instance GHC.Classes.Eq Agda.Syntax.Scope.Monad.ResolvedName instance GHC.Show.Show Agda.Syntax.Scope.Monad.ResolvedName module Agda.TypeChecking.Monad.Sharing updateSharedTerm :: MonadTCM tcm => (Term -> tcm Term) -> Term -> tcm Term updateSharedTermF :: (MonadTCM tcm, Traversable f) => (Term -> tcm (f Term)) -> Term -> tcm (f Term) updateSharedTermT :: (MonadTCM tcm, MonadTrans t, Monad (t tcm)) => (Term -> t tcm Term) -> Term -> t tcm Term forceEqualTerms :: Term -> Term -> TCM () disableDestructiveUpdate :: TCM a -> TCM a module Agda.Syntax.Abstract.Copatterns translateCopatternClauses :: [Clause] -> ScopeM (Delayed, [Clause]) instance GHC.Classes.Ord Agda.Syntax.Abstract.Copatterns.ProjEntry instance GHC.Classes.Eq Agda.Syntax.Abstract.Copatterns.ProjEntry instance GHC.Base.Functor (Agda.Syntax.Abstract.Copatterns.Path a) instance Agda.Syntax.Position.HasRange Agda.Syntax.Abstract.Copatterns.ProjEntry instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.Name.QName instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.Expr instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.LetBinding instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.LamBinding instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.TypedBindings instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.TypedBinding instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.Clause instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.RHS instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.LHS instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.LHSCore instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.Pattern instance Agda.Syntax.Abstract.Copatterns.Rename Agda.Syntax.Abstract.Declaration instance Agda.Syntax.Abstract.Copatterns.Rename a => Agda.Syntax.Abstract.Copatterns.Rename (Agda.Syntax.Abstract.Arg a) instance Agda.Syntax.Abstract.Copatterns.Rename a => Agda.Syntax.Abstract.Copatterns.Rename (Agda.Syntax.Common.Named n a) instance Agda.Syntax.Abstract.Copatterns.Rename a => Agda.Syntax.Abstract.Copatterns.Rename [a] instance (Agda.Syntax.Abstract.Copatterns.Rename a, Agda.Syntax.Abstract.Copatterns.Rename b) => Agda.Syntax.Abstract.Copatterns.Rename (a, b) instance Agda.Syntax.Abstract.Copatterns.Alpha Agda.Syntax.Abstract.Name.Name instance Agda.Syntax.Abstract.Copatterns.Alpha (Agda.Syntax.Abstract.Pattern' e) instance Agda.Syntax.Abstract.Copatterns.Alpha (Agda.Syntax.Abstract.LHSCore' e) instance Agda.Syntax.Abstract.Copatterns.Alpha Agda.Syntax.Abstract.LHS instance Agda.Syntax.Abstract.Copatterns.Alpha a => Agda.Syntax.Abstract.Copatterns.Alpha (Agda.Syntax.Abstract.Arg a) instance (GHC.Classes.Eq n, Agda.Syntax.Abstract.Copatterns.Alpha a) => Agda.Syntax.Abstract.Copatterns.Alpha (Agda.Syntax.Common.Named n a) instance Agda.Syntax.Abstract.Copatterns.Alpha a => Agda.Syntax.Abstract.Copatterns.Alpha [a] module Agda.Syntax.Concrete.Operators.Parser data ExprView e LocalV :: QName -> ExprView e WildV :: e -> ExprView e OtherV :: e -> ExprView e AppV :: e -> (NamedArg e) -> ExprView e -- | The QName is possibly ambiguous, but it must correspond to one -- of the names in the set. OpAppV :: QName -> (Set Name) -> [NamedArg (OpApp e)] -> ExprView e HiddenArgV :: (Named_ e) -> ExprView e InstanceArgV :: (Named_ e) -> ExprView e LamV :: [LamBinding] -> e -> ExprView e ParenV :: e -> ExprView e class HasRange e => IsExpr e exprView :: IsExpr e => e -> ExprView e unExprView :: IsExpr e => ExprView e -> e -- | Parse a specific identifier as a NamePart partP :: IsExpr e => [Name] -> RawName -> ReadP e Range binop :: IsExpr e => ReadP e (NewNotation, Range, [e]) -> ReadP e (e -> e -> e) preop :: IsExpr e => ReadP e (NewNotation, Range, [e]) -> ReadP e (e -> e) postop :: IsExpr e => ReadP e (NewNotation, Range, [e]) -> ReadP e (e -> e) -- | Parse the "operator part" of the given syntax. holes at beginning and -- end are IGNORED. opP :: IsExpr e => ReadP e e -> NewNotation -> ReadP e (NewNotation, Range, [e]) -- | Given a name with a syntax spec, and a list of parsed expressions -- fitting it, rebuild the expression. rebuild :: IsExpr e => NewNotation -> Range -> [e] -> e rebuildBinding :: IsExpr e => ExprView e -> LamBinding -- | Parse using the appropriate fixity, given a parser parsing the -- operator part, the name of the operator, and a parser of -- subexpressions. infixP :: IsExpr e => ReadP e (NewNotation, Range, [e]) -> ReadP e e -> ReadP e e -- | Parse using the appropriate fixity, given a parser parsing the -- operator part, the name of the operator, and a parser of -- subexpressions. infixrP :: IsExpr e => ReadP e (NewNotation, Range, [e]) -> ReadP e e -> ReadP e e -- | Parse using the appropriate fixity, given a parser parsing the -- operator part, the name of the operator, and a parser of -- subexpressions. infixlP :: IsExpr e => ReadP e (NewNotation, Range, [e]) -> ReadP e e -> ReadP e e -- | Parse using the appropriate fixity, given a parser parsing the -- operator part, the name of the operator, and a parser of -- subexpressions. postfixP :: IsExpr e => ReadP e (NewNotation, Range, [e]) -> ReadP e e -> ReadP e e -- | Parse using the appropriate fixity, given a parser parsing the -- operator part, the name of the operator, and a parser of -- subexpressions. prefixP :: IsExpr e => ReadP e (NewNotation, Range, [e]) -> ReadP e e -> ReadP e e -- | Parse using the appropriate fixity, given a parser parsing the -- operator part, the name of the operator, and a parser of -- subexpressions. nonfixP :: IsExpr e => ReadP e (NewNotation, Range, [e]) -> ReadP e e -> ReadP e e argsP :: IsExpr e => ReadP e e -> ReadP e [NamedArg e] appP :: IsExpr e => ReadP e e -> ReadP e [NamedArg e] -> ReadP e e atomP :: IsExpr e => (QName -> Bool) -> ReadP e e instance Agda.Syntax.Concrete.Operators.Parser.IsExpr e => Agda.Syntax.Position.HasRange (Agda.Syntax.Concrete.Operators.Parser.ExprView e) instance Agda.Syntax.Concrete.Operators.Parser.IsExpr Agda.Syntax.Concrete.Expr instance Agda.Syntax.Concrete.Operators.Parser.IsExpr Agda.Syntax.Concrete.Pattern -- | The parser doesn't know about operators and parses everything as -- normal function application. This module contains the functions that -- parses the operators properly. For a stand-alone implementation of -- this see src/prototyping/mixfix/old. -- -- It also contains the function that puts parenthesis back given the -- precedence of the context. module Agda.Syntax.Concrete.Operators -- | Parse a list of expressions into an application. parseApplication :: [Expr] -> ScopeM Expr -- | Parse an expression into a module application (an identifier plus a -- list of arguments). parseModuleApplication :: Expr -> ScopeM (QName, [NamedArg Expr]) -- | Parses a left-hand side, and makes sure that it defined the expected -- name. parseLHS :: Name -> Pattern -> ScopeM LHSCore -- | Parses a pattern. parsePattern :: Pattern -> ScopeM Pattern parsePatternSyn :: Pattern -> ScopeM Pattern module Agda.TypeChecking.Monad.Trace interestingCall :: Closure Call -> Bool traceCallM :: MonadTCM tcm => tcm Call -> tcm a -> tcm a -- | Record a function call in the trace. traceCall :: MonadTCM tcm => Call -> tcm a -> tcm a traceCallCPS :: MonadTCM tcm => Call -> (r -> tcm a) -> ((r -> tcm a) -> tcm b) -> tcm b traceCallCPS_ :: MonadTCM tcm => Call -> tcm a -> (tcm a -> tcm b) -> tcm b getCurrentRange :: TCM Range -- | Sets the current range (for error messages etc.) to the range of the -- given object, if it has a range (i.e., its range is not -- noRange). setCurrentRange :: HasRange x => x -> TCM a -> TCM a module Agda.TypeChecking.Monad.Env -- | Get the name of the current module, if any. currentModule :: TCM ModuleName -- | Set the name of the current module. withCurrentModule :: ModuleName -> TCM a -> TCM a -- | Get the number of variables bound by anonymous modules. getAnonymousVariables :: ModuleName -> TCM Nat -- | Add variables bound by an anonymous module. withAnonymousModule :: ModuleName -> Nat -> TCM a -> TCM a -- | Set the current environment to the given withEnv :: TCEnv -> TCM a -> TCM a -- | Get the current environment getEnv :: TCM TCEnv -- | Increases the module nesting level by one in the given computation. withIncreasedModuleNestingLevel :: TCM a -> TCM a -- | Set highlighting level withHighlightingLevel :: HighlightingLevel -> TCM a -> TCM a -- | Restore setting for ExpandLast to default. doExpandLast :: TCM a -> TCM a dontExpandLast :: TCM a -> TCM a -- | If the reduced did a proper match (constructor or literal pattern), -- then record this as simplification step. performedSimplification :: MonadReader TCEnv m => m a -> m a performedSimplification' :: MonadReader TCEnv m => Simplification -> m a -> m a getSimplification :: MonadReader TCEnv m => m Simplification -- | Lens for AllowedReductions. updateAllowedReductions :: (AllowedReductions -> AllowedReductions) -> TCEnv -> TCEnv modifyAllowedReductions :: (AllowedReductions -> AllowedReductions) -> TCM a -> TCM a putAllowedReductions :: AllowedReductions -> TCM a -> TCM a -- | Reduce Def f vs only if f is a projection. onlyReduceProjections :: TCM a -> TCM a -- | Allow all reductions except for non-terminating functions (default). allowAllReductions :: TCM a -> TCM a -- | Allow all reductions including non-terminating functions. allowNonTerminatingReductions :: TCM a -> TCM a insideDotPattern :: TCM a -> TCM a isInsideDotPattern :: TCM Bool isReifyingUnquoted :: TCM Bool nowReifyingUnquoted :: TCM a -> TCM a module Agda.TypeChecking.LevelConstraints -- | simplifyLevelConstraint n c cs turns an c into an -- equality constraint if it is an inequality constraint and the reverse -- inequality is contained in cs. Number n is the -- length of the context c is defined in. simplifyLevelConstraint :: Int -> Constraint -> Constraints -> Constraint instance GHC.Classes.Eq Agda.TypeChecking.LevelConstraints.Leq instance GHC.Show.Show Agda.TypeChecking.LevelConstraints.Leq -- | Basically a copy of the ErrorT monad transformer. It's handy to slap -- onto TCM and still be a MonadTCM (which isn't possible with ErrorT). module Agda.TypeChecking.Monad.Exception newtype ExceptionT err m a ExceptionT :: m (Either err a) -> ExceptionT err m a [runExceptionT] :: ExceptionT err m a -> m (Either err a) class Error err => MonadException err m | m -> err throwException :: MonadException err m => err -> m a catchException :: MonadException err m => m a -> (err -> m a) -> m a instance (GHC.Base.Monad m, Agda.Utils.Except.Error err) => GHC.Base.Monad (Agda.TypeChecking.Monad.Exception.ExceptionT err m) instance (GHC.Base.Monad m, Agda.Utils.Except.Error err) => Agda.TypeChecking.Monad.Exception.MonadException err (Agda.TypeChecking.Monad.Exception.ExceptionT err m) instance (GHC.Base.Monad m, Agda.TypeChecking.Monad.Exception.MonadException err m) => Agda.TypeChecking.Monad.Exception.MonadException err (Control.Monad.Trans.Reader.ReaderT r m) instance (GHC.Base.Monad m, Agda.TypeChecking.Monad.Exception.MonadException err m, GHC.Base.Monoid w) => Agda.TypeChecking.Monad.Exception.MonadException err (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance Control.Monad.Trans.Class.MonadTrans (Agda.TypeChecking.Monad.Exception.ExceptionT err) instance GHC.Base.Functor f => GHC.Base.Functor (Agda.TypeChecking.Monad.Exception.ExceptionT err f) instance (Agda.Utils.Except.Error err, GHC.Base.Applicative m, GHC.Base.Monad m) => GHC.Base.Applicative (Agda.TypeChecking.Monad.Exception.ExceptionT err m) instance (Agda.Utils.Except.Error err, Control.Monad.State.Class.MonadState s m) => Control.Monad.State.Class.MonadState s (Agda.TypeChecking.Monad.Exception.ExceptionT err m) instance (Agda.Utils.Except.Error err, Control.Monad.Reader.Class.MonadReader r m) => Control.Monad.Reader.Class.MonadReader r (Agda.TypeChecking.Monad.Exception.ExceptionT err m) instance (Agda.Utils.Except.Error err, Control.Monad.Error.Class.MonadError err' m) => Control.Monad.Error.Class.MonadError err' (Agda.TypeChecking.Monad.Exception.ExceptionT err m) instance (Agda.Utils.Except.Error err, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Agda.TypeChecking.Monad.Exception.ExceptionT err m) instance (Agda.Utils.Except.Error err, Agda.TypeChecking.Monad.Base.MonadTCM tcm) => Agda.TypeChecking.Monad.Base.MonadTCM (Agda.TypeChecking.Monad.Exception.ExceptionT err tcm) module Agda.TypeChecking.Monad.Closure enterClosure :: Closure a -> (a -> TCM b) -> TCM b module Agda.TypeChecking.Monad.Constraints -- | Get the current problem currentProblem :: TCM ProblemId -- | Steal all constraints belonging to the given problem and add them to -- the current problem. stealConstraints :: ProblemId -> TCM () solvingProblem :: ProblemId -> TCM a -> TCM a isProblemSolved :: ProblemId -> TCM Bool getConstraintsForProblem :: ProblemId -> TCM Constraints -- | Get the awake constraints getAwakeConstraints :: TCM Constraints wakeConstraints :: (ProblemConstraint -> Bool) -> TCM () dropConstraints :: (ProblemConstraint -> Bool) -> TCM () putAllConstraintsToSleep :: TCM () takeAwakeConstraint :: TCM (Maybe ProblemConstraint) getAllConstraints :: TCM Constraints withConstraint :: (Constraint -> TCM a) -> ProblemConstraint -> TCM a buildProblemConstraint :: ProblemId -> Constraint -> TCM ProblemConstraint buildConstraint :: Constraint -> TCM ProblemConstraint -- | Add new a constraint addConstraint' :: Constraint -> TCM () -- | Add already awake constraints addAwakeConstraints :: Constraints -> TCM () -- | Start solving constraints nowSolvingConstraints :: TCM a -> TCM a isSolvingConstraints :: TCM Bool mapAwakeConstraints :: (Constraints -> Constraints) -> TCState -> TCState mapSleepingConstraints :: (Constraints -> Constraints) -> TCState -> TCState modifyAwakeConstraints :: (Constraints -> Constraints) -> TCM () modifySleepingConstraints :: (Constraints -> Constraints) -> TCM () module Agda.TypeChecking.Monad.Open -- | Create an open term in the current context. makeOpen :: a -> TCM (Open a) -- | Create an open term which is closed. makeClosed :: a -> Open a -- | Extract the value from an open term. Must be done in an extension of -- the context in which the term was created. getOpen :: Subst a => Open a -> TCM a -- | Try to use an Open the current context. Returns Nothing -- if current context is not an extension of the context in which the -- Open was created. tryOpen :: Subst a => Open a -> TCM (Maybe a) module Agda.TypeChecking.Monad.Context -- | Modify the ctxEntry field of a ContextEntry. modifyContextEntry :: (Dom (Name, Type) -> Dom (Name, Type)) -> ContextEntry -> ContextEntry -- | Modify all ContextEntrys. modifyContextEntries :: (Dom (Name, Type) -> Dom (Name, Type)) -> Context -> Context -- | Modify a Context in a computation. modifyContext :: MonadTCM tcm => (Context -> Context) -> tcm a -> tcm a mkContextEntry :: MonadTCM tcm => Dom (Name, Type) -> tcm ContextEntry -- | Change the context. inContext :: MonadTCM tcm => [Dom (Name, Type)] -> tcm a -> tcm a -- | Change to top (=empty) context. inTopContext :: MonadTCM tcm => tcm a -> tcm a -- | Delete the last n bindings from the context. escapeContext :: MonadTCM tcm => Int -> tcm a -> tcm a -- | addCtx x arg cont add a variable to the context. -- -- Chooses an unused Name. addCtx :: MonadTCM tcm => Name -> Dom Type -> tcm a -> tcm a -- | Various specializations of addCtx. class AddContext b addContext :: (AddContext b, MonadTCM tcm) => b -> tcm a -> tcm a -- | add a bunch of variables with the same type to the context addCtxs :: MonadTCM tcm => [Name] -> Dom Type -> tcm a -> tcm a -- | Turns the string into a name and adds it to the context. addCtxString :: MonadTCM tcm => String -> Dom Type -> tcm a -> tcm a -- | Turns the string into a name and adds it to the context, with dummy -- type. addCtxString_ :: MonadTCM tcm => String -> tcm a -> tcm a addCtxStrings_ :: MonadTCM tcm => [String] -> tcm a -> tcm a -- | Context entries without a type have this dummy type. dummyDom :: Dom Type -- | Go under an abstraction. underAbstraction :: (Subst a, MonadTCM tcm) => Dom Type -> Abs a -> (a -> tcm b) -> tcm b -- | Go under an abstract without worrying about the type to add to the -- context. underAbstraction_ :: (Subst a, MonadTCM tcm) => Abs a -> (a -> tcm b) -> tcm b -- | Add a telescope to the context. addCtxTel :: MonadTCM tcm => Telescope -> tcm a -> tcm a -- | Add a let bound variable addLetBinding :: MonadTCM tcm => ArgInfo -> Name -> Term -> Type -> tcm a -> tcm a -- | Get the current context. getContext :: MonadTCM tcm => tcm [Dom (Name, Type)] -- | Get the size of the current context. getContextSize :: MonadTCM tcm => tcm Nat -- | Generate [var (n - 1), ..., var 0] for all declarations in -- the context. getContextArgs :: MonadTCM tcm => tcm Args -- | Generate [var (n - 1), ..., var 0] for all declarations in -- the context. getContextTerms :: MonadTCM tcm => tcm [Term] -- | Get the current context as a Telescope. getContextTelescope :: MonadTCM tcm => tcm Telescope -- | Check if we are in a compatible context, i.e. an extension of the -- given context. getContextId :: MonadTCM tcm => tcm [CtxId] -- | get type of bound variable (i.e. deBruijn index) lookupBV :: MonadTCM tcm => Nat -> tcm (Dom (Name, Type)) typeOfBV' :: MonadTCM tcm => Nat -> tcm (Dom Type) typeOfBV :: MonadTCM tcm => Nat -> tcm Type nameOfBV :: MonadTCM tcm => Nat -> tcm Name -- | Get the term corresponding to a named variable. If it is a lambda -- bound variable the deBruijn index is returned and if it is a let bound -- variable its definition is returned. getVarInfo :: MonadTCM tcm => Name -> tcm (Term, Dom Type) instance Agda.TypeChecking.Monad.Context.AddContext a => Agda.TypeChecking.Monad.Context.AddContext [a] instance Agda.TypeChecking.Monad.Context.AddContext (Agda.Syntax.Abstract.Name.Name, Agda.Syntax.Internal.Dom Agda.Syntax.Internal.Type) instance Agda.TypeChecking.Monad.Context.AddContext (Agda.Syntax.Internal.Dom (Agda.Syntax.Abstract.Name.Name, Agda.Syntax.Internal.Type)) instance Agda.TypeChecking.Monad.Context.AddContext ([Agda.Syntax.Abstract.Name.Name], Agda.Syntax.Internal.Dom Agda.Syntax.Internal.Type) instance Agda.TypeChecking.Monad.Context.AddContext ([Agda.Syntax.Common.WithHiding Agda.Syntax.Abstract.Name.Name], Agda.Syntax.Internal.Dom Agda.Syntax.Internal.Type) instance Agda.TypeChecking.Monad.Context.AddContext (GHC.Base.String, Agda.Syntax.Internal.Dom Agda.Syntax.Internal.Type) instance Agda.TypeChecking.Monad.Context.AddContext (Agda.Syntax.Internal.Dom (GHC.Base.String, Agda.Syntax.Internal.Type)) instance Agda.TypeChecking.Monad.Context.AddContext (Agda.Syntax.Internal.Dom Agda.Syntax.Internal.Type) instance Agda.TypeChecking.Monad.Context.AddContext Agda.Syntax.Abstract.Name.Name instance Agda.TypeChecking.Monad.Context.AddContext GHC.Base.String instance Agda.TypeChecking.Monad.Context.AddContext Agda.Syntax.Internal.Telescope module Agda.TypeChecking.Monad.MetaVars -- | Switch off assignment of metas. dontAssignMetas :: TCM a -> TCM a -- | Get the meta store. getMetaStore :: TCM MetaStore modifyMetaStore :: (MetaStore -> MetaStore) -> TCM () -- | Lookup a meta variable lookupMeta :: MetaId -> TCM MetaVariable updateMetaVar :: MetaId -> (MetaVariable -> MetaVariable) -> TCM () getMetaPriority :: MetaId -> TCM MetaPriority isSortMeta :: MetaId -> TCM Bool isSortMeta_ :: MetaVariable -> Bool getMetaType :: MetaId -> TCM Type -- | Given a meta, return the type applied to the current context. getMetaTypeInContext :: MetaId -> TCM Type -- | Check whether all metas are instantiated. Precondition: argument is a -- meta (in some form) or a list of metas. class IsInstantiatedMeta a isInstantiatedMeta :: IsInstantiatedMeta a => a -> TCM Bool -- | Does not worry about raising. isInstantiatedMeta' :: MetaId -> TCM (Maybe Term) -- | Create MetaInfo in the current environment. createMetaInfo :: TCM MetaInfo createMetaInfo' :: RunMetaOccursCheck -> TCM MetaInfo setValueMetaName :: Term -> MetaNameSuggestion -> TCM () getMetaNameSuggestion :: MetaId -> TCM MetaNameSuggestion setMetaNameSuggestion :: MetaId -> MetaNameSuggestion -> TCM () updateMetaVarRange :: MetaId -> Range -> TCM () modifyInteractionPoints :: (InteractionPoints -> InteractionPoints) -> TCM () -- | Register an interaction point during scope checking. If there is no -- interaction id yet, create one. registerInteractionPoint :: Range -> Maybe Nat -> TCM InteractionId -- | Hook up meta variable to interaction point. connectInteractionPoint :: InteractionId -> MetaId -> TCM () -- | Move an interaction point from the current ones to the old ones. removeInteractionPoint :: InteractionId -> TCM () -- | Get a list of interaction ids. getInteractionPoints :: TCM [InteractionId] -- | Get all metas that correspond to interaction ids. getInteractionMetas :: TCM [MetaId] -- | Get all metas that correspond to interaction ids. getInteractionIdsAndMetas :: TCM [(InteractionId, MetaId)] -- | Does the meta variable correspond to an interaction point? -- -- Time: O(n) where n is the number of interaction -- metas. isInteractionMeta :: MetaId -> TCM (Maybe InteractionId) -- | Get the information associated to an interaction point. lookupInteractionPoint :: InteractionId -> TCM InteractionPoint -- | Get MetaId for an interaction point. Precondition: interaction -- point is connected. lookupInteractionId :: InteractionId -> TCM MetaId -- | Generate new meta variable. newMeta :: MetaInfo -> MetaPriority -> Permutation -> Judgement a -> TCM MetaId -- | Generate a new meta variable with some instantiation given. For -- instance, the instantiation could be a -- PostponedTypeCheckingProblem. newMeta' :: MetaInstantiation -> MetaInfo -> MetaPriority -> Permutation -> Judgement a -> TCM MetaId -- | Get the Range for an interaction point. getInteractionRange :: InteractionId -> TCM Range -- | Get the Range for a meta variable. getMetaRange :: MetaId -> TCM Range getInteractionScope :: InteractionId -> TCM ScopeInfo withMetaInfo' :: MetaVariable -> TCM a -> TCM a withMetaInfo :: Closure Range -> TCM a -> TCM a getInstantiatedMetas :: TCM [MetaId] getOpenMetas :: TCM [MetaId] -- | listenToMeta l m: register l as a listener to -- m. This is done when the type of l is blocked by m. listenToMeta :: Listener -> MetaId -> TCM () -- | Unregister a listener. unlistenToMeta :: Listener -> MetaId -> TCM () -- | Get the listeners to a meta. getMetaListeners :: MetaId -> TCM [Listener] clearMetaListeners :: MetaId -> TCM () -- | Freeze all so far unfrozen metas for the duration of the given -- computation. withFreezeMetas :: TCM a -> TCM a -- | Freeze all meta variables and return the list of metas that got -- frozen. freezeMetas :: TCM [MetaId] -- | Thaw all meta variables. unfreezeMetas :: TCM () -- | Thaw some metas, as indicated by the passed condition. unfreezeMetas' :: (MetaId -> Bool) -> TCM () isFrozen :: MetaId -> TCM Bool -- | Unfreeze meta and its type if this is a meta again. Does not unfreeze -- deep occurrences of metas. class UnFreezeMeta a unfreezeMeta :: UnFreezeMeta a => a -> TCM () instance Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta Agda.Syntax.Common.MetaId instance Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta Agda.Syntax.Internal.Term instance Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta Agda.Syntax.Internal.Level instance Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta a => Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta [a] instance Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta a => Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta (GHC.Base.Maybe a) instance Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta a => Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta (Agda.Syntax.Common.Arg c a) instance Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta a => Agda.TypeChecking.Monad.MetaVars.IsInstantiatedMeta (Agda.Syntax.Internal.Abs a) instance Agda.TypeChecking.Monad.MetaVars.UnFreezeMeta Agda.Syntax.Common.MetaId instance Agda.TypeChecking.Monad.MetaVars.UnFreezeMeta Agda.Syntax.Internal.Type instance Agda.TypeChecking.Monad.MetaVars.UnFreezeMeta Agda.Syntax.Internal.Term instance Agda.TypeChecking.Monad.MetaVars.UnFreezeMeta Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Monad.MetaVars.UnFreezeMeta Agda.Syntax.Internal.Level instance Agda.TypeChecking.Monad.MetaVars.UnFreezeMeta Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Monad.MetaVars.UnFreezeMeta Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.Monad.MetaVars.UnFreezeMeta a => Agda.TypeChecking.Monad.MetaVars.UnFreezeMeta [a] instance Agda.TypeChecking.Monad.MetaVars.UnFreezeMeta a => Agda.TypeChecking.Monad.MetaVars.UnFreezeMeta (Agda.Syntax.Internal.Abs a) module Agda.TypeChecking.Monad.Imports addImport :: ModuleName -> TCM () addImportCycleCheck :: TopLevelModuleName -> TCM a -> TCM a getImports :: TCM (Set ModuleName) isImported :: ModuleName -> TCM Bool getImportPath :: TCM [TopLevelModuleName] visitModule :: ModuleInfo -> TCM () setVisitedModules :: VisitedModules -> TCM () getVisitedModules :: TCM VisitedModules isVisited :: TopLevelModuleName -> TCM Bool getVisitedModule :: TopLevelModuleName -> TCM (Maybe ModuleInfo) getDecodedModules :: TCM DecodedModules setDecodedModules :: DecodedModules -> TCM () getDecodedModule :: TopLevelModuleName -> TCM (Maybe Interface) storeDecodedModule :: Interface -> TCM () dropDecodedModule :: TopLevelModuleName -> TCM () withImportPath :: [TopLevelModuleName] -> TCM a -> TCM a -- | Assumes that the first module in the import path is the module we are -- worried about. checkForImportCycle :: TCM () module Agda.TypeChecking.Monad.Mutual noMutualBlock :: TCM a -> TCM a inMutualBlock :: TCM a -> TCM a -- | Set the mutual block for a definition setMutualBlock :: MutualId -> QName -> TCM () -- | Get all mutual blocks getMutualBlocks :: TCM [Set QName] -- | Get the current mutual block, if any, otherwise a fresh mutual block -- is returned. currentOrFreshMutualBlock :: TCM MutualId lookupMutualBlock :: MutualId -> TCM (Set QName) findMutualBlock :: QName -> TCM (Set QName) module Agda.TypeChecking.Monad.Signature -- | Add a constant to the signature. Lifts the definition to top level. addConstant :: QName -> Definition -> TCM () -- | Set termination info of a defined function symbol. setTerminates :: QName -> Bool -> TCM () -- | Modify the clauses of a function. modifyFunClauses :: QName -> ([Clause] -> [Clause]) -> TCM () -- | Lifts clauses to the top-level and adds them to definition. addClauses :: QName -> [Clause] -> TCM () addHaskellCode :: QName -> HaskellType -> HaskellCode -> TCM () addHaskellExport :: QName -> HaskellType -> String -> TCM () addHaskellType :: QName -> HaskellType -> TCM () addEpicCode :: QName -> EpicCode -> TCM () addJSCode :: QName -> String -> TCM () markStatic :: QName -> TCM () unionSignatures :: [Signature] -> Signature -- | Add a section to the signature. -- -- The current context will be stored as the cumulative module parameters -- for this section. addSection :: ModuleName -> TCM () -- | Lookup a section. If it doesn't exist that just means that the module -- wasn't parameterised. lookupSection :: ModuleName -> TCM Telescope addDisplayForms :: QName -> TCM () -- | Module application (followed by module parameter abstraction). applySection :: ModuleName -> Telescope -> ModuleName -> Args -> Ren QName -> Ren ModuleName -> TCM () applySection' :: ModuleName -> Telescope -> ModuleName -> Args -> Ren QName -> Ren ModuleName -> TCM () -- | Add a display form to a definition (could be in this or imported -- signature). addDisplayForm :: QName -> DisplayForm -> TCM () canonicalName :: QName -> TCM QName sameDef :: QName -> QName -> TCM (Maybe QName) -- | Can be called on either a (co)datatype, a record type or a -- (co)constructor. whatInduction :: QName -> TCM Induction -- | Does the given constructor come from a single-constructor type? -- -- Precondition: The name has to refer to a constructor. singleConstructorType :: QName -> TCM Bool class (Functor m, Applicative m, Monad m) => HasConstInfo m -- | Lookup the definition of a name. The result is a closed thing, all -- free variables have been abstracted over. getConstInfo :: HasConstInfo m => QName -> m Definition -- | Lookup the rewrite rules with the given head symbol. getRewriteRulesFor :: HasConstInfo m => QName -> m RewriteRules defaultGetRewriteRulesFor :: (Monad m) => m TCState -> QName -> m RewriteRules getConInfo :: MonadTCM tcm => ConHead -> tcm Definition -- | Look up the polarity of a definition. getPolarity :: QName -> TCM [Polarity] -- | Look up polarity of a definition and compose with polarity represented -- by Comparison. getPolarity' :: Comparison -> QName -> TCM [Polarity] -- | Set the polarity of a definition. setPolarity :: QName -> [Polarity] -> TCM () -- | Get argument occurrence info for argument i of definition -- d (never fails). getArgOccurrence :: QName -> Nat -> TCM Occurrence setArgOccurrences :: QName -> [Occurrence] -> TCM () modifyArgOccurrences :: QName -> ([Occurrence] -> [Occurrence]) -> TCM () -- | Get the mutually recursive identifiers. getMutual :: QName -> TCM [QName] -- | Set the mutually recursive identifiers. setMutual :: QName -> [QName] -> TCM () -- | Check whether two definitions are mutually recursive. mutuallyRecursive :: QName -> QName -> TCM Bool -- | Why Maybe? The reason is that we look up all prefixes of a module to -- compute number of parameters, and for hierarchical top-level modules, -- A.B.C say, A and A.B do not exist. getSection :: ModuleName -> TCM (Maybe Section) -- | Get the number of parameters to the current module. getCurrentModuleFreeVars :: TCM Nat -- | Compute the number of free variables of a defined name. This is the -- sum of number of parameters shared with the current module and the -- number of anonymous variables (if the name comes from a let-bound -- module). getDefFreeVars :: QName -> TCM Nat -- | Compute the context variables to apply a definition to. freeVarsToApply :: QName -> TCM Args -- | Instantiate a closed definition with the correct part of the current -- context. instantiateDef :: Definition -> TCM Definition -- | Give the abstract view of a definition. makeAbstract :: Definition -> Maybe Definition -- | Enter abstract mode. Abstract definition in the current module are -- transparent. inAbstractMode :: TCM a -> TCM a -- | Not in abstract mode. All abstract definitions are opaque. inConcreteMode :: TCM a -> TCM a -- | Ignore abstract mode. All abstract definitions are transparent. ignoreAbstractMode :: MonadReader TCEnv m => m a -> m a -- | Enter concrete or abstract mode depending on whether the given -- identifier is concrete or abstract. inConcreteOrAbstractMode :: QName -> TCM a -> TCM a -- | Check whether a name might have to be treated abstractly (either if -- we're inAbstractMode or it's not a local name). Returns true -- for things not declared abstract as well, but for those -- makeAbstract will have no effect. treatAbstractly :: MonadReader TCEnv m => QName -> m Bool -- | Andreas, 2015-07-01: If the current module is a weak suffix -- of the identifier module, we can see through its abstract definition -- if we are abstract. (Then treatAbstractly' returns -- False). -- -- If I am not mistaken, then we cannot see definitions in the -- where block of an abstract function from the perspective of -- the function, because then the current module is a strict prefix of -- the module of the local identifier. This problem is fixed by removing -- trailing anonymous module name parts (underscores) from both names. treatAbstractly' :: QName -> TCEnv -> Bool -- | Get type of a constant, instantiated to the current context. typeOfConst :: QName -> TCM Type -- | Get relevance of a constant. relOfConst :: QName -> TCM Relevance -- | Get colors of a constant. colOfConst :: QName -> TCM [Color] -- | The name must be a datatype. sortOfConst :: QName -> TCM Sort -- | The number of parameters of a definition. defPars :: Definition -> Int -- | The number of dropped parameters for a definition. 0 except for -- projection(-like) functions and constructors. droppedPars :: Definition -> Int -- | Is it the name of a record projection? isProjection :: HasConstInfo m => QName -> m (Maybe Projection) isProjection_ :: Defn -> Maybe Projection -- | Returns True if we are dealing with a proper projection, -- i.e., not a projection-like function nor a record field value -- (projection applied to argument). isProperProjection :: Defn -> Bool -- | Number of dropped initial arguments of a projection(-like) function. projectionArgs :: Defn -> Int -- | Check whether a definition uses copatterns. usesCopatterns :: QName -> TCM Bool -- | Apply a function f to its first argument, producing the -- proper postfix projection if f is a projection. applyDef :: QName -> Arg Term -> TCM Term -- | getDefType f t computes the type of (possibly -- projection-(like)) function t whose first argument has type -- t. The parameters for f are extracted from -- t. Nothing if f is projection(like) but -- t is not a datarecordaxiom type. -- -- Precondition: t is reduced. -- -- See also: getConType getDefType :: QName -> Type -> TCM (Maybe Type) instance Agda.TypeChecking.Monad.Signature.HasConstInfo (Agda.TypeChecking.Monad.Base.TCMT GHC.Types.IO) instance (Agda.TypeChecking.Monad.Signature.HasConstInfo m, Agda.Utils.Except.Error err) => Agda.TypeChecking.Monad.Signature.HasConstInfo (Agda.TypeChecking.Monad.Exception.ExceptionT err m) -- | Stuff for sized types that does not require modules -- Agda.TypeChecking.Reduce or -- Agda.TypeChecking.Constraints (which import -- Agda.TypeChecking.Monad). module Agda.TypeChecking.Monad.SizedTypes -- | Result of querying whether size variable i is bounded by -- another size. data BoundedSize -- | yes i : Size< t BoundedLt :: Term -> BoundedSize BoundedNo :: BoundedSize -- | Check if a type is the primSize type. The argument should be -- reduced. isSizeType :: Type -> TCM (Maybe BoundedSize) isSizeTypeTest :: TCM (Type -> Maybe BoundedSize) getBuiltinDefName :: String -> TCM (Maybe QName) getBuiltinSize :: TCM (Maybe QName, Maybe QName) isSizeNameTest :: TCM (QName -> Bool) isSizeNameTestRaw :: TCM (QName -> Bool) -- | Test whether OPTIONS --sized-types and whether the size built-ins are -- defined. haveSizedTypes :: TCM Bool -- | Add polarity info to a SIZE builtin. builtinSizeHook :: String -> QName -> Type -> TCM () -- | The sort of built-in types SIZE and SIZELT. sizeSort :: Sort -- | The type of built-in types SIZE and SIZELT. sizeUniv :: Type -- | The built-in type SIZE with user-given name. sizeType_ :: QName -> Type -- | The built-in type SIZE. sizeType :: TCM Type -- | The name of SIZESUC. sizeSucName :: TCM (Maybe QName) sizeSuc :: Nat -> Term -> TCM Term sizeSuc_ :: QName -> Term -> Term -- | Transform list of terms into a term build from binary maximum. sizeMax :: [Term] -> TCM Term -- | A useful view on sizes. data SizeView SizeInf :: SizeView SizeSuc :: Term -> SizeView OtherSize :: Term -> SizeView sizeView :: Term -> TCM SizeView type Offset = Nat -- | A deep view on sizes. data DeepSizeView DSizeInf :: DeepSizeView DSizeVar :: Nat -> Offset -> DeepSizeView DSizeMeta :: MetaId -> Elims -> Offset -> DeepSizeView DOtherSize :: Term -> DeepSizeView data SizeViewComparable a NotComparable :: SizeViewComparable a YesAbove :: DeepSizeView -> a -> SizeViewComparable a YesBelow :: DeepSizeView -> a -> SizeViewComparable a -- | sizeViewComparable v w checks whether v >= w -- (then Left) or v <= w (then Right). If -- uncomparable, it returns NotComparable. sizeViewComparable :: DeepSizeView -> DeepSizeView -> SizeViewComparable () sizeViewSuc_ :: QName -> DeepSizeView -> DeepSizeView -- | sizeViewPred k v decrements v by k (must be -- possible!). sizeViewPred :: Nat -> DeepSizeView -> DeepSizeView -- | sizeViewOffset v returns the number of successors or Nothing -- when infty. sizeViewOffset :: DeepSizeView -> Maybe Offset -- | Remove successors common to both sides. removeSucs :: (DeepSizeView, DeepSizeView) -> (DeepSizeView, DeepSizeView) -- | Turn a size view into a term. unSizeView :: SizeView -> TCM Term unDeepSizeView :: DeepSizeView -> TCM Term type SizeMaxView = [DeepSizeView] maxViewMax :: SizeMaxView -> SizeMaxView -> SizeMaxView -- | maxViewCons v ws = max v ws. It only adds v to -- ws if it is not subsumed by an element of ws. maxViewCons :: DeepSizeView -> SizeMaxView -> SizeMaxView -- | sizeViewComparableWithMax v ws tries to find w in -- ws that compares with v and singles this out. -- Precondition: v /= DSizeInv. sizeViewComparableWithMax :: DeepSizeView -> SizeMaxView -> SizeViewComparable SizeMaxView maxViewSuc_ :: QName -> SizeMaxView -> SizeMaxView unMaxView :: SizeMaxView -> TCM Term instance GHC.Base.Functor Agda.TypeChecking.Monad.SizedTypes.SizeViewComparable instance GHC.Show.Show Agda.TypeChecking.Monad.SizedTypes.DeepSizeView instance GHC.Show.Show Agda.TypeChecking.Monad.SizedTypes.BoundedSize instance GHC.Classes.Eq Agda.TypeChecking.Monad.SizedTypes.BoundedSize -- | Collect statistics. module Agda.TypeChecking.Monad.Statistics -- | Increase specified counter by 1. tick :: String -> TCM () -- | Increase specified counter by n. tickN :: String -> Integer -> TCM () -- | Set the specified counter to the maximum of its current value and -- n. tickMax :: String -> Integer -> TCM () -- | Get the statistics. getStatistics :: TCM Statistics -- | Modify the statistics via given function. modifyStatistics :: (Statistics -> Statistics) -> TCM () -- | Print the given statistics if verbosity "profile" is given. printStatistics :: Int -> Maybe TopLevelModuleName -> Statistics -> TCM () module Agda.TypeChecking.Monad module Agda.Syntax.Abstract.Pretty showA :: (Show c, ToConcrete a c) => a -> TCM String prettyA :: (Pretty c, ToConcrete a c) => a -> TCM Doc prettyAs :: (Pretty c, ToConcrete a [c]) => a -> TCM Doc -- | Variant of showA which does not insert outermost parentheses. showATop :: (Show c, ToConcrete a c) => a -> TCM String -- | Variant of prettyA which does not insert outermost parentheses. prettyATop :: (Pretty c, ToConcrete a c) => a -> TCM Doc -- | A command which calls a compiler module Agda.Compiler.CallCompiler -- | Calls a compiler: -- -- callCompiler :: FilePath -> [String] -> TCM () -- | Generalisation of callCompiler where the raised exception is -- returned. callCompiler' :: FilePath -> [String] -> TCM (Maybe String) module Agda.Compiler.MAlonzo.Misc setInterface :: Interface -> TCM () curIF :: TCM Interface curSig :: TCM Signature curMName :: TCM ModuleName curHsMod :: TCM ModuleName curDefs :: TCM Definitions sigMName :: Signature -> ModuleName ihname :: String -> Nat -> Name unqhname :: String -> QName -> Name tlmodOf :: ModuleName -> TCM ModuleName tlmname :: ModuleName -> TCM ModuleName xqual :: QName -> Name -> TCM QName xhqn :: String -> QName -> TCM QName conhqn :: QName -> TCM QName bltQual :: String -> String -> TCM QName dsubname :: QName -> Nat -> Name hsVarUQ :: Name -> Exp mazstr :: String mazName :: Name mazMod' :: String -> ModuleName mazMod :: ModuleName -> ModuleName mazerror :: String -> a mazCoerce :: Exp mazIncompleteMatch :: Exp rtmIncompleteMatch :: QName -> Exp mazRTE :: ModuleName rtmMod :: ModuleName rtmQual :: String -> QName rtmVar :: String -> Exp rtmError :: String -> Exp unsafeCoerceMod :: ModuleName fakeD :: Name -> String -> Decl fakeDS :: String -> String -> Decl fakeDQ :: QName -> String -> Decl fakeType :: String -> Type fakeExp :: String -> Exp dummy :: a emptyBinds :: Binds module Agda.Compiler.MAlonzo.Encode -- | Haskell module names have to satisfy the Haskell (including the -- hierarchical module namespace extension) lexical syntax: -- --
--   modid -> [modid.] large {small | large | digit | ' }
--   
-- -- encodeModuleName is an injective function into the set of -- module names defined by modid. The function preserves -- .s, and it also preserves module names whose first name part -- is not mazstr. -- -- Precondition: The input must not start or end with ., and no -- two .s may be adjacent. encodeModuleName :: ModuleName -> ModuleName -- | All the properties. tests :: IO Bool instance GHC.Show.Show Agda.Compiler.MAlonzo.Encode.M instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Compiler.MAlonzo.Encode.M module Agda.Compiler.MAlonzo.Pretty -- | Encodes module names just before pretty-printing. prettyPrint :: (Pretty a, TransformBi ModuleName (Wrap a)) => a -> String -- | A wrapper type used to avoid orphan instances. newtype Wrap a Wrap :: a -> Wrap a [unwrap] :: Wrap a -> a instance Data.Generics.Geniplate.TransformBi Language.Haskell.Exts.Syntax.ModuleName (Agda.Compiler.MAlonzo.Pretty.Wrap Language.Haskell.Exts.Syntax.QName) instance Data.Generics.Geniplate.TransformBi Language.Haskell.Exts.Syntax.ModuleName (Agda.Compiler.MAlonzo.Pretty.Wrap Language.Haskell.Exts.Syntax.ModuleName) instance Data.Generics.Geniplate.TransformBi Language.Haskell.Exts.Syntax.ModuleName (Agda.Compiler.MAlonzo.Pretty.Wrap Language.Haskell.Exts.Syntax.Module) instance Data.Generics.Geniplate.TransformBi Language.Haskell.Exts.Syntax.ModuleName (Agda.Compiler.MAlonzo.Pretty.Wrap Language.Haskell.Exts.Syntax.Exp) -- | Irrelevant function types. module Agda.TypeChecking.Irrelevance -- | Prepare parts of a parameter telescope for abstraction in constructors -- and projections. hideAndRelParams :: Dom a -> Dom a -- | Used to modify context when going into a rel argument. inverseApplyRelevance :: Relevance -> Dom a -> Dom a -- | Compose two relevance flags. This function is used to update the -- relevance information on pattern variables a after a match -- against something rel. applyRelevance :: Relevance -> Dom a -> Dom a -- | Modify the context whenever going from the l.h.s. (term side) of the -- typing judgement to the r.h.s. (type side). workOnTypes :: TCM a -> TCM a -- | Call me if --experimental-irrelevance is set. doWorkOnTypes :: TCM a -> TCM a -- | Internal workhorse, expects value of --experimental-irrelevance flag -- as argument. workOnTypes' :: Bool -> TCM a -> TCM a -- | (Conditionally) wake up irrelevant variables and make them relevant. -- For instance, in an irrelevant function argument otherwise irrelevant -- variables may be used, so they are awoken before type checking the -- argument. applyRelevanceToContext :: Relevance -> TCM a -> TCM a -- | Wake up irrelevant variables and make them relevant. For instance, in -- an irrelevant function argument otherwise irrelevant variables may be -- used, so they are awoken before type checking the argument. wakeIrrelevantVars :: TCM a -> TCM a prop_galois :: Relevance -> Relevance -> Relevance -> Bool tests :: IO Bool module Agda.Interaction.Monad -- | Interaction monad. type IM = TCMT (InputT IO) runIM :: IM a -> TCM a -- | Line reader. The line reader history is not stored between sessions. readline :: String -> IM (Maybe String) -- | Functions which give precise syntax highlighting info to Emacs. module Agda.Interaction.Highlighting.Emacs -- | Turns syntax highlighting information into a list of S-expressions. lispifyHighlightingInfo :: HighlightingInfo -> ModuleToSource -> TCM (Lisp String) -- | All the properties. tests :: IO Bool -- | Generate an import dependency graph for a given module. module Agda.Interaction.Highlighting.Dot -- | Internal module identifiers for construction of dependency graph. type ModuleId = String data DotState DotState :: Map ModuleName ModuleId -> [ModuleId] -> Set (ModuleId, ModuleId) -> DotState -- | Records already processed modules and maps them to an internal -- identifier. [dsModules] :: DotState -> Map ModuleName ModuleId -- | Supply of internal identifiers. [dsNameSupply] :: DotState -> [ModuleId] -- | Edges of dependency graph. [dsConnection] :: DotState -> Set (ModuleId, ModuleId) initialDotState :: DotState type DotM = StateT DotState TCM -- | Translate a ModuleName to an internal ModuleId. Returns -- True if the ModuleName is new, i.e., has not been -- encountered before and is thus added to the map of processed modules. addModule :: ModuleName -> DotM (ModuleId, Bool) -- | Add an arc from importer to imported. addConnection :: ModuleId -> ModuleId -> DotM () -- | Recursively build import graph, starting from given Interface. -- Modifies the state in DotM and returns the ModuleId of -- the Interface. dottify :: Interface -> DotM ModuleId -- | Generate a .dot file for the import graph starting with the given -- Interface and write it to the file specified by the command -- line option. generateDot :: Interface -> TCM () -- | Function for generating highlighted, hyperlinked HTML from Agda -- sources. module Agda.Interaction.Highlighting.HTML -- | Generates HTML files from all the sources which have been visited -- during the type checking phase. -- -- This function should only be called after type checking has completed -- successfully. generateHTML :: TCM () -- | The name of the default CSS file. defaultCSSFile :: FilePath -- | Prepare information for HTML page generation. -- -- The page generator receives the file path of the module, the top level -- module name of the module and the highlighting information of the -- module. generateHTMLWithPageGen :: (FilePath -> TopLevelModuleName -> CompressedFile -> TCM ()) -> TCM () -- | Generates a highlighted, hyperlinked version of the given module. generatePage :: (FilePath -> FilePath -> String -> String) -> FilePath -> TopLevelModuleName -> TCM () -- | Constructs the web page, including headers. page :: FilePath -> TopLevelModuleName -> Html -> String -- | Constructs token stream ready to print. tokenStream :: String -> CompressedFile -> [(Int, String, Aspects)] -- | Constructs the HTML displaying the code. code :: [(Int, String, Aspects)] -> Html module Agda.Interaction.Highlighting.Vim vimFile :: FilePath -> FilePath escape :: String -> String wordBounded :: String -> String keyword :: String -> [String] -> String match :: String -> [String] -> String matches :: [String] -> [String] -> [String] -> [String] -> [String] -> [String] -> [String] toVim :: NamesInScope -> String generateVimFile :: FilePath -> TCM () -- | Function for generating highlighted and aligned LaTeX from literate -- Agda source. module Agda.Interaction.Highlighting.LaTeX -- | The only exported function. It's (only) called in Main.hs. generateLaTeX :: TopLevelModuleName -> HighlightingInfo -> TCM () instance GHC.Show.Show Agda.Interaction.Highlighting.LaTeX.Debug instance GHC.Classes.Eq Agda.Interaction.Highlighting.LaTeX.Debug instance GHC.Show.Show Agda.Interaction.Highlighting.LaTeX.Token module Agda.Termination.RecCheck recursive :: [QName] -> TCM Bool -- | anysDef names a returns all definitions from names -- that are used in a. anyDefs :: GetDefs a => [QName] -> a -> TCM [QName] module Agda.TypeChecking.Reduce.Monad constructorForm :: Term -> ReduceM Term enterClosure :: Closure a -> (a -> ReduceM b) -> ReduceM b underAbstraction_ :: Subst a => Abs a -> (a -> ReduceM b) -> ReduceM b -- | Lookup the definition of a name. The result is a closed thing, all -- free variables have been abstracted over. getConstInfo :: HasConstInfo m => QName -> m Definition isInstantiatedMeta :: MetaId -> ReduceM Bool lookupMeta :: MetaId -> ReduceM MetaVariable reportSDoc :: VerboseKey -> Int -> TCM Doc -> ReduceM () reportSLn :: VerboseKey -> Int -> String -> ReduceM () traceSLn :: HasOptions m => VerboseKey -> Int -> String -> m a -> m a traceSDoc :: VerboseKey -> Int -> TCM Doc -> ReduceM a -> ReduceM a askR :: ReduceM ReduceEnv -- | Apply a function if a certain verbosity level is activated. -- -- Precondition: The level must be non-negative. applyWhenVerboseS :: HasOptions m => VerboseKey -> Int -> (m a -> m a) -> m a -> m a instance Agda.TypeChecking.Monad.Options.HasOptions Agda.TypeChecking.Monad.Base.ReduceM instance Agda.TypeChecking.Monad.Builtin.HasBuiltins Agda.TypeChecking.Monad.Base.ReduceM instance Agda.TypeChecking.Monad.Signature.HasConstInfo Agda.TypeChecking.Monad.Base.ReduceM -- | Compute eta short normal forms. module Agda.TypeChecking.EtaContract data BinAppView App :: Term -> (Arg Term) -> BinAppView NoApp :: Term -> BinAppView binAppView :: Term -> BinAppView -- | Contracts all eta-redexes it sees without reducing. etaContract :: (MonadReader TCEnv m, HasConstInfo m, TermLike a) => a -> m a etaOnce :: (MonadReader TCEnv m, HasConstInfo m) => Term -> m Term module Agda.TypeChecking.MetaVars.Mention class MentionsMeta t mentionsMeta :: MentionsMeta t => MetaId -> t -> Bool instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta Agda.Syntax.Internal.Term instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta Agda.Syntax.Internal.Level instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta Agda.Syntax.Internal.Type instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta Agda.Syntax.Internal.Sort instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta t => Agda.TypeChecking.MetaVars.Mention.MentionsMeta (Agda.Syntax.Internal.Abs t) instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta t => Agda.TypeChecking.MetaVars.Mention.MentionsMeta (Agda.Syntax.Internal.Arg t) instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta t => Agda.TypeChecking.MetaVars.Mention.MentionsMeta (Agda.Syntax.Internal.Dom t) instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta t => Agda.TypeChecking.MetaVars.Mention.MentionsMeta [t] instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta t => Agda.TypeChecking.MetaVars.Mention.MentionsMeta (GHC.Base.Maybe t) instance (Agda.TypeChecking.MetaVars.Mention.MentionsMeta a, Agda.TypeChecking.MetaVars.Mention.MentionsMeta b) => Agda.TypeChecking.MetaVars.Mention.MentionsMeta (a, b) instance (Agda.TypeChecking.MetaVars.Mention.MentionsMeta a, Agda.TypeChecking.MetaVars.Mention.MentionsMeta b, Agda.TypeChecking.MetaVars.Mention.MentionsMeta c) => Agda.TypeChecking.MetaVars.Mention.MentionsMeta (a, b, c) instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta a => Agda.TypeChecking.MetaVars.Mention.MentionsMeta (Agda.TypeChecking.Monad.Base.Closure a) instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta Agda.Syntax.Internal.Elim instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta a => Agda.TypeChecking.MetaVars.Mention.MentionsMeta (Agda.Syntax.Internal.Tele a) instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta Agda.TypeChecking.Monad.Base.ProblemConstraint instance Agda.TypeChecking.MetaVars.Mention.MentionsMeta Agda.TypeChecking.Monad.Base.Constraint -- | Tools to manipulate patterns in abstract syntax in the TCM (type -- checking monad). module Agda.TypeChecking.Patterns.Abstract -- | Expand literal integer pattern into suc/zero constructor patterns. expandLitPattern :: NamedArg Pattern -> TCM (NamedArg Pattern) -- | Expand away (deeply) all pattern synonyms in a pattern. class ExpandPatternSynonyms a expandPatternSynonyms :: ExpandPatternSynonyms a => a -> TCM a instance Agda.TypeChecking.Patterns.Abstract.ExpandPatternSynonyms a => Agda.TypeChecking.Patterns.Abstract.ExpandPatternSynonyms (GHC.Base.Maybe a) instance Agda.TypeChecking.Patterns.Abstract.ExpandPatternSynonyms a => Agda.TypeChecking.Patterns.Abstract.ExpandPatternSynonyms [a] instance Agda.TypeChecking.Patterns.Abstract.ExpandPatternSynonyms a => Agda.TypeChecking.Patterns.Abstract.ExpandPatternSynonyms (Agda.Syntax.Common.Arg c a) instance Agda.TypeChecking.Patterns.Abstract.ExpandPatternSynonyms a => Agda.TypeChecking.Patterns.Abstract.ExpandPatternSynonyms (Agda.Syntax.Common.Named n a) instance Agda.TypeChecking.Patterns.Abstract.ExpandPatternSynonyms Agda.Syntax.Abstract.Pattern module Agda.TypeChecking.Reduce instantiate :: Instantiate a => a -> TCM a instantiateFull :: InstantiateFull a => a -> TCM a reduce :: Reduce a => a -> TCM a reduceB :: Reduce a => a -> TCM (Blocked a) normalise :: Normalise a => a -> TCM a simplify :: Simplify a => a -> TCM a -- | Instantiate something. Results in an open meta variable or a non meta. -- Doesn't do any reduction, and preserves blocking tags (when blocking -- meta is uninstantiated). class Instantiate t instantiate' :: Instantiate t => t -> ReduceM t -- | Case on whether a term is blocked on a meta (or is a meta). That means -- it can change its shape when the meta is instantiated. ifBlocked :: MonadTCM tcm => Term -> (MetaId -> Term -> tcm a) -> (Term -> tcm a) -> tcm a -- | Case on whether a type is blocked on a meta (or is a meta). ifBlockedType :: MonadTCM tcm => Type -> (MetaId -> Type -> tcm a) -> (Type -> tcm a) -> tcm a class Reduce t where reduce' t = ignoreBlocking <$> reduceB' t reduceB' t = notBlocked <$> reduce' t reduce' :: Reduce t => t -> ReduceM t reduceB' :: Reduce t => t -> ReduceM (Blocked t) rewriteAfter :: (Term -> ReduceM (Blocked Term)) -> Term -> ReduceM (Blocked Term) unfoldCorecursionE :: Elim -> ReduceM (Blocked Elim) unfoldCorecursion :: Term -> ReduceM (Blocked Term) -- | If the first argument is True, then a single delayed clause may -- be unfolded. unfoldDefinition :: Bool -> (Term -> ReduceM (Blocked Term)) -> Term -> QName -> Args -> ReduceM (Blocked Term) unfoldDefinitionE :: Bool -> (Term -> ReduceM (Blocked Term)) -> Term -> QName -> Elims -> ReduceM (Blocked Term) unfoldDefinition' :: Bool -> (Term -> ReduceM (Simplification, Blocked Term)) -> Term -> QName -> Elims -> ReduceM (Simplification, Blocked Term) -- | Reduce a non-primitive definition if it is a copy linking to another -- def. reduceDefCopy :: QName -> Args -> TCM (Reduced () Term) -- | Reduce simple (single clause) definitions. reduceHead :: Term -> TCM (Blocked Term) reduceHead' :: Term -> ReduceM (Blocked Term) -- | Apply a definition using the compiled clauses, or fall back to -- ordinary clauses if no compiled clauses exist. appDef_ :: QName -> Term -> [Clause] -> Maybe CompiledClauses -> MaybeReducedArgs -> ReduceM (Reduced (Blocked Term) Term) appDefE_ :: QName -> Term -> [Clause] -> Maybe CompiledClauses -> MaybeReducedElims -> ReduceM (Reduced (Blocked Term) Term) -- | Apply a defined function to it's arguments, using the compiled -- clauses. The original term is the first argument applied to the third. appDef :: Term -> CompiledClauses -> MaybeReducedArgs -> ReduceM (Reduced (Blocked Term) Term) appDefE :: Term -> CompiledClauses -> MaybeReducedElims -> ReduceM (Reduced (Blocked Term) Term) -- | Apply a defined function to it's arguments, using the original -- clauses. appDef' :: Term -> [Clause] -> MaybeReducedArgs -> ReduceM (Reduced (Blocked Term) Term) appDefE' :: Term -> [Clause] -> MaybeReducedElims -> ReduceM (Reduced (Blocked Term) Term) -- | Only unfold definitions if this leads to simplification which means -- that a constructor/literal pattern is matched. class Simplify t simplify' :: Simplify t => t -> ReduceM t simplifyBlocked' :: Simplify t => Blocked t -> ReduceM t class Normalise t normalise' :: Normalise t => t -> ReduceM t -- | instantiateFull' instantiates metas everywhere (and -- recursively) but does not reduce. class InstantiateFull t instantiateFull' :: InstantiateFull t => t -> ReduceM t instance Agda.TypeChecking.Reduce.Instantiate Agda.Syntax.Internal.Term instance Agda.TypeChecking.Reduce.Instantiate Agda.Syntax.Internal.Level instance Agda.TypeChecking.Reduce.Instantiate Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Reduce.Instantiate Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.Reduce.Instantiate a => Agda.TypeChecking.Reduce.Instantiate (Agda.Syntax.Internal.Blocked a) instance Agda.TypeChecking.Reduce.Instantiate Agda.Syntax.Internal.Type instance Agda.TypeChecking.Reduce.Instantiate Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Reduce.Instantiate Agda.Syntax.Internal.Elim instance Agda.TypeChecking.Reduce.Instantiate t => Agda.TypeChecking.Reduce.Instantiate (Agda.Syntax.Internal.Abs t) instance Agda.TypeChecking.Reduce.Instantiate t => Agda.TypeChecking.Reduce.Instantiate (Agda.Syntax.Internal.Arg t) instance Agda.TypeChecking.Reduce.Instantiate t => Agda.TypeChecking.Reduce.Instantiate (Agda.Syntax.Internal.Dom t) instance Agda.TypeChecking.Reduce.Instantiate t => Agda.TypeChecking.Reduce.Instantiate [t] instance (Agda.TypeChecking.Reduce.Instantiate a, Agda.TypeChecking.Reduce.Instantiate b) => Agda.TypeChecking.Reduce.Instantiate (a, b) instance (Agda.TypeChecking.Reduce.Instantiate a, Agda.TypeChecking.Reduce.Instantiate b, Agda.TypeChecking.Reduce.Instantiate c) => Agda.TypeChecking.Reduce.Instantiate (a, b, c) instance Agda.TypeChecking.Reduce.Instantiate a => Agda.TypeChecking.Reduce.Instantiate (Agda.TypeChecking.Monad.Base.Closure a) instance Agda.TypeChecking.Reduce.Instantiate Agda.Syntax.Internal.Telescope instance Agda.TypeChecking.Reduce.Instantiate Agda.TypeChecking.Monad.Base.Constraint instance (GHC.Classes.Ord k, Agda.TypeChecking.Reduce.Instantiate e) => Agda.TypeChecking.Reduce.Instantiate (Data.Map.Base.Map k e) instance Agda.TypeChecking.Reduce.Reduce Agda.Syntax.Internal.Type instance Agda.TypeChecking.Reduce.Reduce Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Reduce.Reduce Agda.Syntax.Internal.Elim instance Agda.TypeChecking.Reduce.Reduce Agda.Syntax.Internal.Level instance Agda.TypeChecking.Reduce.Reduce Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Reduce.Reduce Agda.Syntax.Internal.LevelAtom instance (Agda.TypeChecking.Substitute.Subst t, Agda.TypeChecking.Reduce.Reduce t) => Agda.TypeChecking.Reduce.Reduce (Agda.Syntax.Internal.Abs t) instance Agda.TypeChecking.Reduce.Reduce t => Agda.TypeChecking.Reduce.Reduce [t] instance Agda.TypeChecking.Reduce.Reduce t => Agda.TypeChecking.Reduce.Reduce (Agda.Syntax.Internal.Arg t) instance Agda.TypeChecking.Reduce.Reduce t => Agda.TypeChecking.Reduce.Reduce (Agda.Syntax.Internal.Dom t) instance (Agda.TypeChecking.Reduce.Reduce a, Agda.TypeChecking.Reduce.Reduce b) => Agda.TypeChecking.Reduce.Reduce (a, b) instance (Agda.TypeChecking.Reduce.Reduce a, Agda.TypeChecking.Reduce.Reduce b, Agda.TypeChecking.Reduce.Reduce c) => Agda.TypeChecking.Reduce.Reduce (a, b, c) instance Agda.TypeChecking.Reduce.Reduce Agda.Syntax.Internal.Term instance Agda.TypeChecking.Reduce.Reduce a => Agda.TypeChecking.Reduce.Reduce (Agda.TypeChecking.Monad.Base.Closure a) instance Agda.TypeChecking.Reduce.Reduce Agda.Syntax.Internal.Telescope instance Agda.TypeChecking.Reduce.Reduce Agda.TypeChecking.Monad.Base.Constraint instance (GHC.Classes.Ord k, Agda.TypeChecking.Reduce.Reduce e) => Agda.TypeChecking.Reduce.Reduce (Data.Map.Base.Map k e) instance Agda.TypeChecking.Reduce.Simplify Agda.Syntax.Internal.Term instance Agda.TypeChecking.Reduce.Simplify Agda.Syntax.Internal.Type instance Agda.TypeChecking.Reduce.Simplify Agda.Syntax.Internal.Elim instance Agda.TypeChecking.Reduce.Simplify Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Reduce.Simplify Agda.Syntax.Internal.Level instance Agda.TypeChecking.Reduce.Simplify Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Reduce.Simplify Agda.Syntax.Internal.LevelAtom instance (Agda.TypeChecking.Substitute.Subst t, Agda.TypeChecking.Reduce.Simplify t) => Agda.TypeChecking.Reduce.Simplify (Agda.Syntax.Internal.Abs t) instance Agda.TypeChecking.Reduce.Simplify t => Agda.TypeChecking.Reduce.Simplify (Agda.Syntax.Internal.Arg t) instance Agda.TypeChecking.Reduce.Simplify t => Agda.TypeChecking.Reduce.Simplify (Agda.Syntax.Common.Named name t) instance Agda.TypeChecking.Reduce.Simplify t => Agda.TypeChecking.Reduce.Simplify (Agda.Syntax.Internal.Dom t) instance Agda.TypeChecking.Reduce.Simplify t => Agda.TypeChecking.Reduce.Simplify [t] instance (GHC.Classes.Ord k, Agda.TypeChecking.Reduce.Simplify e) => Agda.TypeChecking.Reduce.Simplify (Data.Map.Base.Map k e) instance Agda.TypeChecking.Reduce.Simplify a => Agda.TypeChecking.Reduce.Simplify (GHC.Base.Maybe a) instance (Agda.TypeChecking.Reduce.Simplify a, Agda.TypeChecking.Reduce.Simplify b) => Agda.TypeChecking.Reduce.Simplify (a, b) instance (Agda.TypeChecking.Reduce.Simplify a, Agda.TypeChecking.Reduce.Simplify b, Agda.TypeChecking.Reduce.Simplify c) => Agda.TypeChecking.Reduce.Simplify (a, b, c) instance Agda.TypeChecking.Reduce.Simplify a => Agda.TypeChecking.Reduce.Simplify (Agda.TypeChecking.Monad.Base.Closure a) instance (Agda.TypeChecking.Substitute.Subst a, Agda.TypeChecking.Reduce.Simplify a) => Agda.TypeChecking.Reduce.Simplify (Agda.Syntax.Internal.Tele a) instance Agda.TypeChecking.Reduce.Simplify Agda.TypeChecking.Monad.Base.ProblemConstraint instance Agda.TypeChecking.Reduce.Simplify Agda.TypeChecking.Monad.Base.Constraint instance Agda.TypeChecking.Reduce.Simplify GHC.Types.Bool instance Agda.TypeChecking.Reduce.Simplify Agda.Syntax.Internal.ClauseBody instance Agda.TypeChecking.Reduce.Simplify Agda.TypeChecking.Monad.Base.DisplayForm instance Agda.TypeChecking.Reduce.Normalise Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Reduce.Normalise Agda.Syntax.Internal.Type instance Agda.TypeChecking.Reduce.Normalise Agda.Syntax.Internal.Term instance Agda.TypeChecking.Reduce.Normalise Agda.Syntax.Internal.Elim instance Agda.TypeChecking.Reduce.Normalise Agda.Syntax.Internal.Level instance Agda.TypeChecking.Reduce.Normalise Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Reduce.Normalise Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.Reduce.Normalise Agda.Syntax.Internal.ClauseBody instance (Agda.TypeChecking.Substitute.Subst t, Agda.TypeChecking.Reduce.Normalise t) => Agda.TypeChecking.Reduce.Normalise (Agda.Syntax.Internal.Abs t) instance Agda.TypeChecking.Reduce.Normalise t => Agda.TypeChecking.Reduce.Normalise (Agda.Syntax.Internal.Arg t) instance Agda.TypeChecking.Reduce.Normalise t => Agda.TypeChecking.Reduce.Normalise (Agda.Syntax.Common.Named name t) instance Agda.TypeChecking.Reduce.Normalise t => Agda.TypeChecking.Reduce.Normalise (Agda.Syntax.Internal.Dom t) instance Agda.TypeChecking.Reduce.Normalise t => Agda.TypeChecking.Reduce.Normalise [t] instance (Agda.TypeChecking.Reduce.Normalise a, Agda.TypeChecking.Reduce.Normalise b) => Agda.TypeChecking.Reduce.Normalise (a, b) instance (Agda.TypeChecking.Reduce.Normalise a, Agda.TypeChecking.Reduce.Normalise b, Agda.TypeChecking.Reduce.Normalise c) => Agda.TypeChecking.Reduce.Normalise (a, b, c) instance Agda.TypeChecking.Reduce.Normalise a => Agda.TypeChecking.Reduce.Normalise (Agda.TypeChecking.Monad.Base.Closure a) instance (Agda.TypeChecking.Substitute.Subst a, Agda.TypeChecking.Reduce.Normalise a) => Agda.TypeChecking.Reduce.Normalise (Agda.Syntax.Internal.Tele a) instance Agda.TypeChecking.Reduce.Normalise Agda.TypeChecking.Monad.Base.ProblemConstraint instance Agda.TypeChecking.Reduce.Normalise Agda.TypeChecking.Monad.Base.Constraint instance Agda.TypeChecking.Reduce.Normalise GHC.Types.Bool instance Agda.TypeChecking.Reduce.Normalise Agda.Syntax.Internal.ConPatternInfo instance Agda.TypeChecking.Reduce.Normalise Agda.Syntax.Internal.Pattern instance Agda.TypeChecking.Reduce.Normalise Agda.TypeChecking.Monad.Base.DisplayForm instance (GHC.Classes.Ord k, Agda.TypeChecking.Reduce.Normalise e) => Agda.TypeChecking.Reduce.Normalise (Data.Map.Base.Map k e) instance Agda.TypeChecking.Reduce.Normalise a => Agda.TypeChecking.Reduce.Normalise (GHC.Base.Maybe a) instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Abstract.Name.Name instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Reduce.InstantiateFull a => Agda.TypeChecking.Reduce.InstantiateFull (Agda.Syntax.Internal.Type' a) instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Internal.Term instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Internal.Level instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Internal.Substitution instance Agda.TypeChecking.Reduce.InstantiateFull GHC.Types.Bool instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Internal.ConPatternInfo instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Internal.Pattern instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Internal.ClauseBody instance (Agda.TypeChecking.Substitute.Subst t, Agda.TypeChecking.Reduce.InstantiateFull t) => Agda.TypeChecking.Reduce.InstantiateFull (Agda.Syntax.Internal.Abs t) instance Agda.TypeChecking.Reduce.InstantiateFull t => Agda.TypeChecking.Reduce.InstantiateFull (Agda.Syntax.Internal.Arg t) instance Agda.TypeChecking.Reduce.InstantiateFull t => Agda.TypeChecking.Reduce.InstantiateFull (Agda.Syntax.Common.Named name t) instance Agda.TypeChecking.Reduce.InstantiateFull t => Agda.TypeChecking.Reduce.InstantiateFull (Agda.Syntax.Internal.Dom t) instance Agda.TypeChecking.Reduce.InstantiateFull t => Agda.TypeChecking.Reduce.InstantiateFull [t] instance (Agda.TypeChecking.Reduce.InstantiateFull a, Agda.TypeChecking.Reduce.InstantiateFull b) => Agda.TypeChecking.Reduce.InstantiateFull (a, b) instance (Agda.TypeChecking.Reduce.InstantiateFull a, Agda.TypeChecking.Reduce.InstantiateFull b, Agda.TypeChecking.Reduce.InstantiateFull c) => Agda.TypeChecking.Reduce.InstantiateFull (a, b, c) instance Agda.TypeChecking.Reduce.InstantiateFull a => Agda.TypeChecking.Reduce.InstantiateFull (Agda.TypeChecking.Monad.Base.Closure a) instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.ProblemConstraint instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.Constraint instance Agda.TypeChecking.Reduce.InstantiateFull a => Agda.TypeChecking.Reduce.InstantiateFull (Agda.Syntax.Internal.Elim' a) instance (GHC.Classes.Ord k, Agda.TypeChecking.Reduce.InstantiateFull e) => Agda.TypeChecking.Reduce.InstantiateFull (Data.Map.Base.Map k e) instance (GHC.Classes.Eq k, Data.Hashable.Class.Hashable k, Agda.TypeChecking.Reduce.InstantiateFull e) => Agda.TypeChecking.Reduce.InstantiateFull (Data.HashMap.Base.HashMap k e) instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Abstract.Name.ModuleName instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Scope.Base.Scope instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.Signature instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.Section instance (Agda.TypeChecking.Substitute.Subst a, Agda.TypeChecking.Reduce.InstantiateFull a) => Agda.TypeChecking.Reduce.InstantiateFull (Agda.Syntax.Internal.Tele a) instance Agda.TypeChecking.Reduce.InstantiateFull GHC.Types.Char instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.Definition instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.NLPat instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.RewriteRule instance Agda.TypeChecking.Reduce.InstantiateFull a => Agda.TypeChecking.Reduce.InstantiateFull (Agda.TypeChecking.Monad.Base.Open a) instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.DisplayForm instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.DisplayTerm instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.Defn instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.FunctionInverse instance Agda.TypeChecking.Reduce.InstantiateFull a => Agda.TypeChecking.Reduce.InstantiateFull (Agda.TypeChecking.CompiledClause.WithArity a) instance Agda.TypeChecking.Reduce.InstantiateFull a => Agda.TypeChecking.Reduce.InstantiateFull (Agda.TypeChecking.CompiledClause.Case a) instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.CompiledClause.CompiledClauses instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Internal.Clause instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Monad.Base.Interface instance Agda.TypeChecking.Reduce.InstantiateFull a => Agda.TypeChecking.Reduce.InstantiateFull (Agda.TypeChecking.Monad.Base.Builtin a) instance Agda.TypeChecking.Reduce.InstantiateFull Agda.Syntax.Abstract.Name.QName instance Agda.TypeChecking.Reduce.InstantiateFull a => Agda.TypeChecking.Reduce.InstantiateFull (GHC.Base.Maybe a) module Agda.TypeChecking.Level data LevelKit LevelKit :: Term -> (Term -> Term) -> (Term -> Term -> Term) -> Term -> QName -> QName -> QName -> QName -> LevelKit [lvlType] :: LevelKit -> Term [lvlSuc] :: LevelKit -> Term -> Term [lvlMax] :: LevelKit -> Term -> Term -> Term [lvlZero] :: LevelKit -> Term [typeName] :: LevelKit -> QName [sucName] :: LevelKit -> QName [maxName] :: LevelKit -> QName [zeroName] :: LevelKit -> QName -- | Get the 'primLevel as a Term, if present. mlevel :: TCM (Maybe Term) -- | Get the primLevel as a Type. levelType :: TCM Type levelSucFunction :: TCM (Term -> Term) builtinLevelKit :: TCM (Maybe LevelKit) -- | Raises an error if no level kit is available. requireLevels :: TCM LevelKit unLevel :: Term -> TCM Term reallyUnLevelView :: MonadTCM tcm => Level -> tcm Term unlevelWithKit :: LevelKit -> Level -> Term unPlusV :: Term -> (Term -> Term) -> PlusLevel -> Term maybePrimCon :: TCM Term -> TCM (Maybe ConHead) maybePrimDef :: TCM Term -> TCM (Maybe QName) levelView :: Term -> TCM Level levelView' :: Term -> ReduceM Level levelLub :: Level -> Level -> Level -- | Tools for DisplayTerm and DisplayForm. module Agda.TypeChecking.DisplayForm -- | Convert a DisplayTerm into a Term. dtermToTerm :: DisplayTerm -> Term -- | Get the arities of all display forms for a name. displayFormArities :: QName -> TCM [Int] -- | Find a matching display form for q vs. In essence this tries -- to reqwrite q vs with any display form q ps --> -- dt and returns the instantiated dt if successful. First -- match wins. displayForm :: QName -> Args -> TCM (Maybe DisplayTerm) -- | Match a DisplayForm q ps = v against q vs. -- Return the DisplayTerm v[us] if the match was -- successful, i.e., vs / ps = Just us. matchDisplayForm :: DisplayForm -> Args -> MaybeT TCM DisplayTerm -- | Class Match for matching a term p in the role of a -- pattern against a term v. -- -- The 0th variable in p plays the role of a place holder -- (pattern variable). Each occurrence of var 0 in p -- stands for a different pattern variable. -- -- The result of matching, if successful, is a list of solutions for the -- pattern variables, in left-to-right order. -- -- The 0th variable is in scope in the input v, but should not -- actually occur! In the output solution, the 0th variable is -- no longer in scope. (It has been substituted by IMPOSSIBLE -- which corresponds to a raise by -1). class Match a match :: Match a => a -> a -> MaybeT TCM [Term] instance Agda.TypeChecking.DisplayForm.Match a => Agda.TypeChecking.DisplayForm.Match [a] instance Agda.TypeChecking.DisplayForm.Match a => Agda.TypeChecking.DisplayForm.Match (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.DisplayForm.Match a => Agda.TypeChecking.DisplayForm.Match (Agda.Syntax.Internal.Elim' a) instance Agda.TypeChecking.DisplayForm.Match Agda.Syntax.Internal.Term instance Agda.TypeChecking.DisplayForm.Match Agda.Syntax.Internal.Sort instance Agda.TypeChecking.DisplayForm.Match Agda.Syntax.Internal.Level module Agda.TypeChecking.Telescope data OutputTypeName OutputTypeName :: QName -> OutputTypeName OutputTypeNameNotYetKnown :: OutputTypeName NoOutputTypeName :: OutputTypeName -- | Strips all Pi's and return the head definition name, if possible. getOutputTypeName :: Type -> TCM OutputTypeName -- | The permutation should permute the corresponding telescope. -- (left-to-right list) renameP :: Subst t => Permutation -> t -> t -- | If permute π : [a]Γ -> [a]Δ, then applySubst (renaming -- π) : Term Γ -> Term Δ renaming :: Permutation -> Substitution -- | If permute π : [a]Γ -> [a]Δ, then applySubst -- (renamingR π) : Term Δ -> Term Γ renamingR :: Permutation -> Substitution -- | Flatten telescope: (Γ : Tel) -> [Type Γ] flattenTel :: Telescope -> [Dom Type] -- | Order a flattened telescope in the correct dependeny order: Γ -> -- Permutation (Γ -> Γ~) -- -- Since reorderTel tel uses free variable analysis of type in -- tel, the telescope should be normalised. reorderTel :: [Dom Type] -> Maybe Permutation reorderTel_ :: [Dom Type] -> Permutation -- | Unflatten: turns a flattened telescope into a proper telescope. Must -- be properly ordered. unflattenTel :: [ArgName] -> [Dom Type] -> Telescope -- | Get the suggested names from a telescope teleNames :: Telescope -> [ArgName] teleArgNames :: Telescope -> [Arg ArgName] teleArgs :: Telescope -> Args -- | A telescope split in two. data SplitTel SplitTel :: Telescope -> Telescope -> Permutation -> SplitTel [firstPart] :: SplitTel -> Telescope [secondPart] :: SplitTel -> Telescope -- | The permutation takes us from the original telescope to firstPart -- ++ secondPart. [splitPerm] :: SplitTel -> Permutation -- | Split a telescope into the part that defines the given variables and -- the part that doesn't. -- -- See prop_splitTelescope. splitTelescope :: VarSet -> Telescope -> SplitTel telView :: Type -> TCM TelView -- | telViewUpTo n t takes off the first n function types -- of t. Takes off all if n < 0. telViewUpTo :: Int -> Type -> TCM TelView -- | telViewUpTo' n p t takes off $t$ the first n (or -- arbitrary many if n < 0) function domains as long as they -- satify p. telViewUpTo' :: Int -> (Dom Type -> Bool) -> Type -> TCM TelView -- | Decomposing a function type. mustBePi :: MonadTCM tcm => Type -> tcm (Dom Type, Abs Type) -- | If the given type is a Pi, pass its parts to the first -- continuation. If not (or blocked), pass the reduced type to the second -- continuation. ifPi :: MonadTCM tcm => Term -> (Dom Type -> Abs Type -> tcm a) -> (Term -> tcm a) -> tcm a -- | If the given type is a Pi, pass its parts to the first -- continuation. If not (or blocked), pass the reduced type to the second -- continuation. ifPiType :: MonadTCM tcm => Type -> (Dom Type -> Abs Type -> tcm a) -> (Type -> tcm a) -> tcm a -- | If the given type is blocked or not a Pi, pass it reduced to -- the first continuation. If it is a Pi, pass its parts to the -- second continuation. ifNotPi :: MonadTCM tcm => Term -> (Term -> tcm a) -> (Dom Type -> Abs Type -> tcm a) -> tcm a -- | If the given type is blocked or not a Pi, pass it reduced to -- the first continuation. If it is a Pi, pass its parts to the -- second continuation. ifNotPiType :: MonadTCM tcm => Type -> (Type -> tcm a) -> (Dom Type -> Abs Type -> tcm a) -> tcm a -- | A safe variant of piApply. piApplyM :: Type -> Args -> TCM Type piApply1 :: MonadTCM tcm => Type -> Term -> tcm Type -- | Given a function type, introduce its domain into the context and -- continue with its codomain. intro1 :: (MonadTCM tcm) => Type -> (Type -> tcm a) -> tcm a addTypedInstance :: QName -> Type -> TCM () resolveUnknownInstanceDefs :: TCM () -- | Try to solve the instance definitions whose type is not yet known, -- report an error if it doesn't work and return the instance table -- otherwise. getInstanceDefs :: TCM InstanceTable module Agda.Auto.Convert norm :: Normalise t => t -> TCM t type O = (Maybe Int, QName) data TMode TMAll :: TMode type MapS a b = (Map a b, [a]) initMapS :: MapS a b popMapS :: (S -> (a, [b])) -> ((a, [b]) -> S -> S) -> TOM (Maybe b) data S S :: MapS QName (TMode, ConstRef O) -> MapS MetaId (Metavar (Exp O) (RefInfo O), Maybe (MExp O, [MExp O]), [MetaId]) -> MapS Int (Maybe (Bool, MExp O, MExp O)) -> Maybe MetaId -> MetaId -> S [sConsts] :: S -> MapS QName (TMode, ConstRef O) [sMetas] :: S -> MapS MetaId (Metavar (Exp O) (RefInfo O), Maybe (MExp O, [MExp O]), [MetaId]) [sEqs] :: S -> MapS Int (Maybe (Bool, MExp O, MExp O)) [sCurMeta] :: S -> Maybe MetaId [sMainMeta] :: S -> MetaId type TOM = StateT S TCM tomy :: MetaId -> [(Bool, QName)] -> [Type] -> TCM ([ConstRef O], [MExp O], Map MetaId (Metavar (Exp O) (RefInfo O), MExp O, [MExp O], [MetaId]), [(Bool, MExp O, MExp O)], Map QName (TMode, ConstRef O)) getConst :: Bool -> QName -> TMode -> TOM (ConstRef O) getdfv :: MetaId -> QName -> TCM Nat getMeta :: MetaId -> TOM (Metavar (Exp O) (RefInfo O)) getEqs :: TCM [(Bool, Term, Term)] copatternsNotImplemented :: TCM a tomyClauses :: [Clause] -> TOM [([Pat O], MExp O)] tomyClause :: Clause -> TOM (Maybe ([Pat O], MExp O)) tomyPat :: Arg Pattern -> TOM (Pat O) tomyBody :: ClauseBodyF Term -> TOM (Maybe (MExp O, Int)) weaken :: Int -> MExp O -> MExp O weakens :: Int -> MArgList O -> MArgList O tomyType :: Type -> TOM (MExp O) tomyExp :: Term -> TOM (MExp O) tomyExps :: Args -> TOM (MM (ArgList O) (RefInfo O)) tomyIneq :: Comparison -> Bool fmType :: MetaId -> Type -> Bool fmExp :: MetaId -> Term -> Bool fmExps :: MetaId -> Args -> Bool fmLevel :: MetaId -> PlusLevel -> Bool cnvh :: LensHiding a => a -> FMode icnvh :: FMode -> ArgInfo frommy :: MExp O -> ExceptT String IO Term frommyType :: MExp O -> ExceptT String IO Type frommyExp :: MExp O -> ExceptT String IO Term frommyExps :: Nat -> MArgList O -> Term -> ExceptT String IO Term abslamvarname :: String modifyAbstractExpr :: Expr -> Expr modifyAbstractClause :: Clause -> Clause constructPats :: Map QName (TMode, ConstRef O) -> MetaId -> Clause -> TCM ([(FMode, MId)], [CSPat O]) frommyClause :: (CSCtx O, [CSPat O], Maybe (MExp O)) -> ExceptT String IO Clause contains_constructor :: [CSPat O] -> Bool etaContractBody :: ClauseBody -> TCM ClauseBody freeIn :: Nat -> MExp o -> Bool negtype :: ConstRef o -> MExp o -> MExp o findClauseDeep :: MetaId -> TCM (Maybe (QName, Clause, Bool)) matchType :: Int -> Int -> Type -> Type -> Maybe (Nat, Nat) instance GHC.Classes.Eq Agda.Auto.Convert.TMode module Agda.TypeChecking.Datatypes -- | Get true constructor with record fields. getConHead :: QName -> TCM ConHead -- | Get true constructor as term. getConTerm :: QName -> TCM Term -- | Get true constructor with fields, expanding literals to constructors -- if possible. getConForm :: QName -> TCM ConHead -- | Augment constructor with record fields (preserve constructor name). -- The true constructor might only surface via reduce. getOrigConHead :: QName -> TCM ConHead -- | Analogous to getConTerm. getOrigConTerm :: QName -> TCM Term -- | Get the name of the datatype constructed by a given constructor. -- Precondition: The argument must refer to a constructor getConstructorData :: HasConstInfo m => QName -> m QName -- | getConType c t computes the constructor parameters from type -- t and returns the instantiated type of constructor -- c. Nothing if t is not a data/record type -- or does not have a constructor c. Precondition: t is -- reduced. getConType :: ConHead -> Type -> TCM (Maybe Type) -- | Return the number of non-parameter arguments to a data constructor, or -- the field names of a record constructor. -- -- For getting just the arity of constructor c, use either -- id size $ getConstructorArity c. getConstructorArity :: QName -> TCM (Either Nat [Arg QName]) -- | Check if a name refers to a datatype or a record with a named -- constructor. isDatatype :: QName -> TCM Bool data DataOrRecord IsData :: DataOrRecord IsRecord :: DataOrRecord -- | Check if a name refers to a datatype or a record. isDataOrRecordType :: QName -> TCM (Maybe DataOrRecord) -- | Precodition: Term is reduced. isDataOrRecord :: Term -> TCM (Maybe QName) getNumberOfParameters :: QName -> TCM (Maybe Nat) instance GHC.Show.Show Agda.TypeChecking.Datatypes.DataOrRecord instance GHC.Classes.Ord Agda.TypeChecking.Datatypes.DataOrRecord instance GHC.Classes.Eq Agda.TypeChecking.Datatypes.DataOrRecord -- | Contains the state monad that the compiler works in and some functions -- for tampering with the state. module Agda.Compiler.Epic.CompileState -- | Stuff we need in our compiler data CompileState CompileState :: [Var] -> Map TopLevelModuleName (EInterface, Set FilePath) -> EInterface -> EInterface -> String -> CompileState [nameSupply] :: CompileState -> [Var] [compiledModules] :: CompileState -> Map TopLevelModuleName (EInterface, Set FilePath) [curModule] :: CompileState -> EInterface [importedModules] :: CompileState -> EInterface [curFun] :: CompileState -> String -- | The initial (empty) state initCompileState :: CompileState -- | Compiler monad type Compile = StateT CompileState -- | When normal errors are not enough epicError :: String -> Compile TCM a -- | Modify the state of the current module's Epic Interface modifyEI :: (EInterface -> EInterface) -> Compile TCM () -- | Get the state of the current module's Epic Interface getsEI :: (EInterface -> a) -> Compile TCM a -- | Returns the type of a definition given its name getType :: QName -> Compile TCM Type -- | Create a name which can be used in Epic code from a QName. unqname :: QName -> Var resetNameSupply :: Compile TCM () getDelayed :: QName -> Compile TCM Bool putDelayed :: QName -> Bool -> Compile TCM () newName :: Compile TCM Var putConstrTag :: QName -> Tag -> Compile TCM () assignConstrTag :: QName -> Compile TCM Tag assignConstrTag' :: QName -> [QName] -> Compile TCM Tag getConData :: QName -> Compile TCM QName getDataCon :: QName -> Compile TCM [QName] getConstrTag :: QName -> Compile TCM Tag getConstrTag' :: QName -> Compile TCM (Maybe Tag) addDefName :: QName -> Compile TCM () topBindings :: Compile TCM (Set Var) getConArity :: QName -> Compile TCM Int putConArity :: QName -> Int -> Compile TCM () putMain :: QName -> Compile TCM () getMain :: Compile TCM Var lookInterface :: (EInterface -> Maybe a) -> Compile TCM a -> Compile TCM a constrInScope :: QName -> Compile TCM Bool getForcedArgs :: QName -> Compile TCM ForcedArgs putForcedArgs :: QName -> ForcedArgs -> Compile TCM () replaceAt :: Int -> [a] -> [a] -> [a] -- | Copy pasted from MAlonzo, HAHA!!! Move somewhere else! constructorArity :: Num a => QName -> TCM a -- | Bind an expression to a fresh variable name bindExpr :: Expr -> (Var -> Compile TCM Expr) -> Compile TCM Expr instance GHC.Show.Show Agda.Compiler.Epic.CompileState.CompileState -- | Perform simple optimisations based on case-laws module Agda.Compiler.Epic.CaseOpts caseOpts :: [Fun] -> Compile TCM [Fun] -- | Run the case-opts on an expression caseOptsExpr :: Expr -> Compile TCM Expr -- | Remove forced arguments from constructors. module Agda.Compiler.Epic.ForceConstrs -- | Check which arguments are forced makeForcedArgs :: Type -> ForcedArgs -- | Remove forced arguments from constructors and branches forceConstrs :: [Fun] -> Compile TCM [Fun] forceFun :: Fun -> Compile TCM Fun -- | Pretty-print the AuxAST to valid Epic code. module Agda.Compiler.Epic.Epic -- | Print a function to an Epic string prettyEpicFun :: MonadTCM m => Fun -> Compile m String -- | Print expression to Epic expression prettyEpic :: Expr -> String -- | Detect if a datatype could be represented as a primitive integer. If -- it has one constructor with no arguments and one with a recursive -- argument this is true. This is done using IrrFilters which filter out -- forced arguments, so for example Fin becomes primitive. module Agda.Compiler.Epic.NatDetection -- | Get a list of all the datatypes that look like nats. The [QName] is on -- the form [zeroConstr, sucConstr] getNatish :: Compile TCM [(ForcedArgs, [QName])] isNatish :: QName -> Defn -> Compile TCM (Maybe (ForcedArgs, [QName])) -- | Count the number of relevant arguments nrRel :: ForcedArgs -> Integer -- | Check if argument n is recursive isRec :: Int -> Type -> QName -> Bool argIsDef :: Type -> QName -> Bool -- | Change constructors and cases on builtins and natish datatypes to use -- primitive data module Agda.Compiler.Epic.Primitive data PrimTransform PrimTF :: Map QName Var -> (Expr -> [Branch] -> Expr) -> PrimTransform [mapCon] :: PrimTransform -> Map QName Var [translateCase] :: PrimTransform -> Expr -> [Branch] -> Expr prZero :: Var prSuc :: Var prTrue :: Var prFalse :: Var prPred :: Var prNatEquality :: Var -- | Change constructors and cases on builtins and natish datatypes to use -- primitive data primitivise :: [Fun] -> Compile TCM [Fun] -- | Map primitive constructors to primitive tags initialPrims :: Compile TCM () -- | Build transforms using the names of builtins getBuiltins :: Compile TCM [PrimTransform] defName :: Term -> QName -- | Translation to primitive integer functions natPrimTF :: ForcedArgs -> [QName] -> PrimTransform -- | Corresponds to a case for natural numbers primNatCaseZS :: Expr -> Expr -> Var -> Expr -> Expr -- | Corresponds to a case with a zero and default branch primNatCaseZD :: Expr -> Expr -> Expr -> Expr -- | Translation to primitive bool functions boolPrimTF :: [QName] -> PrimTransform -- | Change all the primitives in the function using the PrimTransform primFun :: [PrimTransform] -> Fun -> Compile TCM Fun -- | Change all the primitives in an expression using PrimTransform primExpr :: [PrimTransform] -> Expr -> Compile TCM Expr -- | A syntactic equality check that takes meta instantiations into -- account, but does not reduce. It replaces (v, v') <- -- instantiateFull (v, v') v == v' by a more efficient routine -- which only traverses and instantiates the terms as long as they are -- equal. module Agda.TypeChecking.SyntacticEquality -- | Instantiate full as long as things are equal class SynEq a where synEq' a a' = ifEqual (uncurry synEq) (a, a') -- | Syntactic equality check for terms. checkSyntacticEquality v v' = -- do (v,v') <- instantiateFull (v,v') return ((v,v'), v==v') -- only that v,v' are only fully instantiated to the depth where -- they are equal. checkSyntacticEquality :: (SynEq a) => a -> a -> TCM ((a, a), Bool) instance Agda.TypeChecking.SyntacticEquality.SynEq Agda.Syntax.Internal.Term instance Agda.TypeChecking.SyntacticEquality.SynEq Agda.Syntax.Internal.Level instance Agda.TypeChecking.SyntacticEquality.SynEq Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.SyntacticEquality.SynEq Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.SyntacticEquality.SynEq Agda.Syntax.Internal.Sort instance Agda.TypeChecking.SyntacticEquality.SynEq Agda.Syntax.Internal.Type instance Agda.TypeChecking.SyntacticEquality.SynEq a => Agda.TypeChecking.SyntacticEquality.SynEq [a] instance Agda.TypeChecking.SyntacticEquality.SynEq a => Agda.TypeChecking.SyntacticEquality.SynEq (Agda.Syntax.Internal.Elim' a) instance (Agda.TypeChecking.Substitute.Subst a, Agda.TypeChecking.SyntacticEquality.SynEq a) => Agda.TypeChecking.SyntacticEquality.SynEq (Agda.Syntax.Internal.Abs a) instance (Agda.TypeChecking.SyntacticEquality.SynEq a, Agda.TypeChecking.SyntacticEquality.SynEq c) => Agda.TypeChecking.SyntacticEquality.SynEq (Agda.Syntax.Common.Arg c a) instance (Agda.TypeChecking.SyntacticEquality.SynEq a, Agda.TypeChecking.SyntacticEquality.SynEq c) => Agda.TypeChecking.SyntacticEquality.SynEq (Agda.Syntax.Common.Dom c a) instance Agda.TypeChecking.SyntacticEquality.SynEq c => Agda.TypeChecking.SyntacticEquality.SynEq (Agda.Syntax.Common.ArgInfo c) module Agda.TypeChecking.Serialise.Base -- | Constructor tag (maybe omitted) and argument indices. type Node = [Int32] -- | The type of hashtables used in this module. -- -- A very limited amount of testing indicates that CuckooHashTable -- is somewhat slower than BasicHashTable, and that -- LinearHashTable and the hashtables from Data.Hashtable -- are much slower. type HashTable k v = BasicHashTable k v -- | Structure providing fresh identifiers for hash map and counting hash -- map hits (i.e. when no fresh identifier required). data FreshAndReuse FreshAndReuse :: !Int32 -> !Int32 -> FreshAndReuse -- | Number of hash map misses. [farFresh] :: FreshAndReuse -> !Int32 -- | Number of hash map hits. [farReuse] :: FreshAndReuse -> !Int32 farEmpty :: FreshAndReuse lensFresh :: Lens' Int32 FreshAndReuse lensReuse :: Lens' Int32 FreshAndReuse -- | Two QNames are equal if their QNameId is equal. type QNameId = [NameId] -- | Computing a qualified names composed ID. qnameId :: QName -> QNameId -- | State of the the encoder. data Dict Dict :: !(HashTable Node Int32) -> !(HashTable String Int32) -> !(HashTable Integer Int32) -> !(HashTable Double Int32) -> !(HashTable (Ptr Term) Int32) -> !(HashTable NameId Int32) -> !(HashTable QNameId Int32) -> !(IORef FreshAndReuse) -> !(IORef FreshAndReuse) -> !(IORef FreshAndReuse) -> !(IORef FreshAndReuse) -> !(IORef FreshAndReuse) -> !(IORef FreshAndReuse) -> !(IORef FreshAndReuse) -> !(HashTable String Int) -> Bool -> !(HashTable AbsolutePath Int32) -> Dict -- | Written to interface file. [nodeD] :: Dict -> !(HashTable Node Int32) -- | Written to interface file. [stringD] :: Dict -> !(HashTable String Int32) -- | Written to interface file. [integerD] :: Dict -> !(HashTable Integer Int32) -- | Written to interface file. Dicitionaries which are not serialized, but -- provide short cuts to speed up serialization: [doubleD] :: Dict -> !(HashTable Double Int32) -- | Not written to interface file. Andreas, Makoto, AIM XXI Memoizing -- A.Name does not buy us much if we already memoize A.QName. [termD] :: Dict -> !(HashTable (Ptr Term) Int32) -- | Not written to interface file. [nameD] :: Dict -> !(HashTable NameId Int32) -- | Not written to interface file. Fresh UIDs and reuse statistics: [qnameD] :: Dict -> !(HashTable QNameId Int32) [nodeC] :: Dict -> !(IORef FreshAndReuse) [stringC] :: Dict -> !(IORef FreshAndReuse) [integerC] :: Dict -> !(IORef FreshAndReuse) [doubleC] :: Dict -> !(IORef FreshAndReuse) [termC] :: Dict -> !(IORef FreshAndReuse) [nameC] :: Dict -> !(IORef FreshAndReuse) [qnameC] :: Dict -> !(IORef FreshAndReuse) [stats] :: Dict -> !(HashTable String Int) -- | If True collect in stats the quantities of calls to -- icode for each Typeable a. [collectStats] :: Dict -> Bool -- | Not written to interface file. [absPathD] :: Dict -> !(HashTable AbsolutePath Int32) -- | Creates an empty dictionary. emptyDict :: Bool -> IO Dict -- | Universal type, wraps everything. data U U :: !a -> U -- | Univeral memo structure, to introduce sharing during decoding type Memo = HashTable (Int32, TypeRep) U -- | State of the decoder. data St St :: !(Array Int32 Node) -> !(Array Int32 String) -> !(Array Int32 Integer) -> !(Array Int32 Double) -> !Memo -> !ModuleToSource -> [AbsolutePath] -> St -- | Obtained from interface file. [nodeE] :: St -> !(Array Int32 Node) -- | Obtained from interface file. [stringE] :: St -> !(Array Int32 String) -- | Obtained from interface file. [integerE] :: St -> !(Array Int32 Integer) -- | Obtained from interface file. [doubleE] :: St -> !(Array Int32 Double) -- | Created and modified by decoder. Used to introduce sharing while -- deserializing objects. [nodeMemo] :: St -> !Memo -- | Maps module names to file names. Constructed by the decoder. [modFile] :: St -> !ModuleToSource -- | The include directories. [includes] :: St -> [AbsolutePath] -- | Monad used by the encoder. type S a = ReaderT Dict IO a -- | Monad used by the decoder. -- -- TCM is not used because the associated overheads would make -- decoding slower. type R a = ExceptT TypeError (StateT St IO) a -- | Throws an error which is suitable when the data stream is malformed. malformed :: R a class Typeable a => EmbPrj a where icode a = do { tickICode a; icod_ a } icode :: EmbPrj a => a -> S Int32 icod_ :: EmbPrj a => a -> S Int32 value :: EmbPrj a => Int32 -> R a -- | Increase entry for a in stats. tickICode :: Typeable a => a -> S () -- | Data.Binary.runGetState is deprecated in favour of runGetIncremental. -- Reimplementing it in terms of the new function. The new Decoder type -- contains strict byte strings so we need to be careful not to feed the -- entire lazy byte string to the decoder at once. runGetState :: Get a -> ByteString -> ByteOffset -> (a, ByteString, ByteOffset) icodeX :: (Eq k, Hashable k) => (Dict -> HashTable k Int32) -> (Dict -> IORef FreshAndReuse) -> k -> S Int32 icodeInteger :: Integer -> S Int32 icodeDouble :: Double -> S Int32 icodeString :: String -> S Int32 icodeN :: Node -> S Int32 -- | icode only if thing has not seen before. icodeMemo :: (Eq a, Ord a, Hashable a) => (Dict -> HashTable a Int32) -> (Dict -> IORef FreshAndReuse) -> a -> S Int32 -> S Int32 -- | vcase value ix decodes thing represented by ix :: -- Int32 via the valu function and stores it in -- nodeMemo. If ix is present in nodeMemo, -- valu is not used, but the thing is read from nodeMemo -- instead. vcase :: EmbPrj a => (Node -> R a) -> Int32 -> R a icode0 :: Int32 -> S Int32 icode1 :: EmbPrj a => Int32 -> a -> S Int32 icode2 :: (EmbPrj a, EmbPrj b) => Int32 -> a -> b -> S Int32 icode3 :: (EmbPrj a, EmbPrj b, EmbPrj c) => Int32 -> a -> b -> c -> S Int32 icode4 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d) => Int32 -> a -> b -> c -> d -> S Int32 icode5 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e) => Int32 -> a -> b -> c -> d -> e -> S Int32 icode6 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f) => Int32 -> a -> b -> c -> d -> e -> f -> S Int32 icode7 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g) => Int32 -> a -> b -> c -> d -> e -> f -> g -> S Int32 icode8 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h) => Int32 -> a -> b -> c -> d -> e -> f -> g -> h -> S Int32 icode9 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i) => Int32 -> a -> b -> c -> d -> e -> f -> g -> h -> i -> S Int32 icode10 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j) => Int32 -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> S Int32 icode11 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k) => Int32 -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> S Int32 icode12 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k, EmbPrj l) => Int32 -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> S Int32 icode13 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k, EmbPrj l, EmbPrj m) => Int32 -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> S Int32 icode14 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k, EmbPrj l, EmbPrj m, EmbPrj n) => Int32 -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> S Int32 icode0' :: S Int32 icode1' :: EmbPrj a => a -> S Int32 icode2' :: (EmbPrj a, EmbPrj b) => a -> b -> S Int32 icode3' :: (EmbPrj a, EmbPrj b, EmbPrj c) => a -> b -> c -> S Int32 icode4' :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d) => a -> b -> c -> d -> S Int32 icode5' :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e) => a -> b -> c -> d -> e -> S Int32 icode6' :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f) => a -> b -> c -> d -> e -> f -> S Int32 icode7' :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g) => a -> b -> c -> d -> e -> f -> g -> S Int32 icode8' :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h) => a -> b -> c -> d -> e -> f -> g -> h -> S Int32 icode9' :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i) => a -> b -> c -> d -> e -> f -> g -> h -> i -> S Int32 icode10' :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j) => a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> S Int32 icode11' :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k) => a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> S Int32 icode12' :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k, EmbPrj l) => a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> S Int32 icode13' :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k, EmbPrj l, EmbPrj m) => a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> S Int32 icode14' :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k, EmbPrj l, EmbPrj m, EmbPrj n) => a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> S Int32 valu0 :: a -> R a valu1 :: EmbPrj a => (a -> b) -> Int32 -> R b valu2 :: (EmbPrj a, EmbPrj b) => (a -> b -> c) -> Int32 -> Int32 -> R c valu3 :: (EmbPrj a, EmbPrj b, EmbPrj c) => (a -> b -> c -> d) -> Int32 -> Int32 -> Int32 -> R d valu4 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d) => (a -> b -> c -> d -> e) -> Int32 -> Int32 -> Int32 -> Int32 -> R e valu5 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e) => (a -> b -> c -> d -> e -> f) -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> R f valu6 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f) => (a -> b -> c -> d -> e -> f -> g) -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> R g valu7 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g) => (a -> b -> c -> d -> e -> f -> g -> h) -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> R h valu8 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h) => (a -> b -> c -> d -> e -> f -> g -> h -> i) -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> R i valu9 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> R j valu10 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> R k valu11 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> R l valu12 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k, EmbPrj l) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> R m valu13 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k, EmbPrj l, EmbPrj m) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n) -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> R n valu14 :: (EmbPrj a, EmbPrj b, EmbPrj c, EmbPrj d, EmbPrj e, EmbPrj f, EmbPrj g, EmbPrj h, EmbPrj i, EmbPrj j, EmbPrj k, EmbPrj l, EmbPrj m, EmbPrj n) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o) -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> Int32 -> R o module Agda.TypeChecking.Serialise.Instances.Common instance Agda.TypeChecking.Serialise.Base.EmbPrj GHC.Base.String instance Agda.TypeChecking.Serialise.Base.EmbPrj GHC.Integer.Type.Integer instance Agda.TypeChecking.Serialise.Base.EmbPrj GHC.Word.Word64 instance Agda.TypeChecking.Serialise.Base.EmbPrj GHC.Int.Int32 instance Agda.TypeChecking.Serialise.Base.EmbPrj GHC.Types.Int instance Agda.TypeChecking.Serialise.Base.EmbPrj GHC.Types.Char instance Agda.TypeChecking.Serialise.Base.EmbPrj GHC.Types.Double instance Agda.TypeChecking.Serialise.Base.EmbPrj () instance (Agda.TypeChecking.Serialise.Base.EmbPrj a, Agda.TypeChecking.Serialise.Base.EmbPrj b) => Agda.TypeChecking.Serialise.Base.EmbPrj (a, b) instance (Agda.TypeChecking.Serialise.Base.EmbPrj a, Agda.TypeChecking.Serialise.Base.EmbPrj b, Agda.TypeChecking.Serialise.Base.EmbPrj c) => Agda.TypeChecking.Serialise.Base.EmbPrj (a, b, c) instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (GHC.Base.Maybe a) instance Agda.TypeChecking.Serialise.Base.EmbPrj GHC.Types.Bool instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Utils.FileName.AbsolutePath instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Position.Position instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Concrete.Name.TopLevelModuleName instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj [a] instance (GHC.Classes.Ord a, GHC.Classes.Ord b, Agda.TypeChecking.Serialise.Base.EmbPrj a, Agda.TypeChecking.Serialise.Base.EmbPrj b) => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Utils.BiMap.BiMap a b) instance (GHC.Classes.Ord a, Agda.TypeChecking.Serialise.Base.EmbPrj a, Agda.TypeChecking.Serialise.Base.EmbPrj b) => Agda.TypeChecking.Serialise.Base.EmbPrj (Data.Map.Base.Map a b) instance (GHC.Classes.Ord a, Agda.TypeChecking.Serialise.Base.EmbPrj a) => Agda.TypeChecking.Serialise.Base.EmbPrj (Data.Set.Base.Set a) instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Position.Interval instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Position.Range instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Concrete.Name.Name instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Concrete.Name.NamePart instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Concrete.Name.QName instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Fixity.Associativity instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Fixity.Fixity instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Fixity.Fixity' instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Notation.GenPart instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Abstract.Name.QName instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Abstract.Name.AmbiguousQName instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Abstract.Name.ModuleName instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Abstract.Name.Name instance (Agda.TypeChecking.Serialise.Base.EmbPrj s, Agda.TypeChecking.Serialise.Base.EmbPrj t) => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Common.Named s t) instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Common.Ranged a) instance Agda.TypeChecking.Serialise.Base.EmbPrj c => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Common.ArgInfo c) instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Common.NameId instance (GHC.Classes.Eq k, Data.Hashable.Class.Hashable k, Agda.TypeChecking.Serialise.Base.EmbPrj k, Agda.TypeChecking.Serialise.Base.EmbPrj v) => Agda.TypeChecking.Serialise.Base.EmbPrj (Data.HashMap.Base.HashMap k v) instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Common.WithHiding a) instance (Agda.TypeChecking.Serialise.Base.EmbPrj a, Agda.TypeChecking.Serialise.Base.EmbPrj c) => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Common.Arg c a) instance (Agda.TypeChecking.Serialise.Base.EmbPrj a, Agda.TypeChecking.Serialise.Base.EmbPrj c) => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Common.Dom c a) instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Common.Induction instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Common.Hiding instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Common.Relevance instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Common.ConPOrigin instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Literal.Literal instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Common.IsAbstract instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Common.Delayed module Agda.TypeChecking.Serialise.Instances.Abstract instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Scope.Base.Scope instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Scope.Base.NameSpaceId instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Common.Access instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Scope.Base.NameSpace instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Scope.Base.WhyInScope instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Scope.Base.AbstractName instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Scope.Base.AbstractModule instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Scope.Base.KindOfName instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Scope.Base.LocalVar instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Abstract.Expr instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Info.ConPatInfo instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Abstract.Pattern instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Abstract.LamBinding instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Abstract.LetBinding instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Abstract.TypedBindings instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Abstract.TypedBinding instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Fixity.Precedence instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Scope.Base.ScopeInfo module Agda.TypeChecking.Serialise.Instances.Compilers instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.HaskellExport instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.HaskellRepresentation instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.CompiledRepresentation instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Compiler.JS.Syntax.Exp instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Compiler.JS.Syntax.LocalId instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Compiler.JS.Syntax.GlobalId instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Compiler.JS.Syntax.MemberId instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Compiler.Epic.Interface.EInterface instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Compiler.Epic.Interface.InjectiveFun instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Compiler.Epic.Interface.Relevance instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Compiler.Epic.Interface.Forced instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Compiler.Epic.Interface.Tag module Agda.TypeChecking.Serialise.Instances.Highlighting instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Interaction.Highlighting.Range.Range instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Interaction.Highlighting.Precise.NameKind instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Interaction.Highlighting.Precise.Aspect instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Interaction.Highlighting.Precise.OtherAspect instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Interaction.Highlighting.Precise.Aspects instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Interaction.Highlighting.Precise.CompressedFile module Agda.TypeChecking.DropArgs -- | When making a function projection-like, we drop the first n -- arguments. class DropArgs a dropArgs :: DropArgs a => Int -> a -> a -- | NOTE: This creates telescopes with unbound de Bruijn indices. -- | NOTE: does not go into the body, so does not work for recursive -- functions. -- | NOTE: does not work for recursive functions. -- | To drop the first n arguments in a compiled clause, we reduce -- the split argument indices by n and drop n arguments -- from the bodies. NOTE: this only works for non-recursive functions, we -- are not dropping arguments to recursive calls in bodies. instance Agda.TypeChecking.DropArgs.DropArgs a => Agda.TypeChecking.DropArgs.DropArgs (GHC.Base.Maybe a) instance Agda.TypeChecking.DropArgs.DropArgs Agda.Syntax.Internal.Telescope instance Agda.TypeChecking.DropArgs.DropArgs Agda.Utils.Permutation.Permutation instance Agda.TypeChecking.DropArgs.DropArgs Agda.Syntax.Internal.ClauseBody instance Agda.TypeChecking.DropArgs.DropArgs Agda.Syntax.Internal.Clause instance Agda.TypeChecking.DropArgs.DropArgs Agda.TypeChecking.Monad.Base.FunctionInverse instance Agda.TypeChecking.DropArgs.DropArgs Agda.TypeChecking.CompiledClause.CompiledClauses -- | Translating from internal syntax to abstract syntax. Enables nice -- pretty printing of internal syntax. -- -- TODO -- -- module Agda.Syntax.Translation.InternalToAbstract class Reify i a | i -> a where reifyWhen _ = reify reify :: Reify i a => i -> TCM a reifyWhen :: Reify i a => Bool -> i -> TCM a type NamedClause = QNamed Clause reifyPatterns :: Telescope -> Permutation -> [NamedArg Pattern] -> TCM [NamedArg Pattern] instance GHC.Show.Show Agda.Syntax.Translation.InternalToAbstract.DoBind instance GHC.Classes.Eq Agda.Syntax.Translation.InternalToAbstract.DoBind instance GHC.Show.Show Agda.Syntax.Translation.InternalToAbstract.DotBind instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Abstract.Name.Name Agda.Syntax.Abstract.Name.Name instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Abstract.Expr Agda.Syntax.Abstract.Expr instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Common.MetaId Agda.Syntax.Abstract.Expr instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.TypeChecking.Monad.Base.DisplayTerm Agda.Syntax.Abstract.Expr instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Literal.Literal Agda.Syntax.Abstract.Expr instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Internal.Term Agda.Syntax.Abstract.Expr instance Agda.Syntax.Translation.InternalToAbstract.Reify i a => Agda.Syntax.Translation.InternalToAbstract.Reify (Agda.Syntax.Common.Named n i) (Agda.Syntax.Common.Named n a) instance Agda.Syntax.Translation.InternalToAbstract.Reify i a => Agda.Syntax.Translation.InternalToAbstract.Reify (Agda.Syntax.Internal.Arg i) (Agda.Syntax.Abstract.Arg a) instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Internal.Elim Agda.Syntax.Abstract.Expr instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Internal.ClauseBody Agda.Syntax.Abstract.RHS instance (GHC.Classes.Ord k, GHC.Base.Monoid v) => GHC.Base.Monoid (Agda.Syntax.Translation.InternalToAbstract.MonoidMap k v) instance Agda.Syntax.Translation.InternalToAbstract.DotVars a => Agda.Syntax.Translation.InternalToAbstract.DotVars (Agda.Syntax.Abstract.Arg a) instance Agda.Syntax.Translation.InternalToAbstract.DotVars a => Agda.Syntax.Translation.InternalToAbstract.DotVars (Agda.Syntax.Common.Named s a) instance Agda.Syntax.Translation.InternalToAbstract.DotVars a => Agda.Syntax.Translation.InternalToAbstract.DotVars [a] instance (Agda.Syntax.Translation.InternalToAbstract.DotVars a, Agda.Syntax.Translation.InternalToAbstract.DotVars b) => Agda.Syntax.Translation.InternalToAbstract.DotVars (a, b) instance Agda.Syntax.Translation.InternalToAbstract.DotVars Agda.Syntax.Abstract.Clause instance Agda.Syntax.Translation.InternalToAbstract.DotVars Agda.Syntax.Abstract.Pattern instance Agda.Syntax.Translation.InternalToAbstract.DotVars Agda.Syntax.Abstract.Expr instance Agda.Syntax.Translation.InternalToAbstract.DotVars Agda.Syntax.Abstract.RHS instance Agda.Syntax.Translation.InternalToAbstract.DotVars Agda.Syntax.Abstract.TypedBindings instance Agda.Syntax.Translation.InternalToAbstract.DotVars Agda.Syntax.Abstract.TypedBinding instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Translation.InternalToAbstract.NamedClause Agda.Syntax.Abstract.Clause instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Internal.Type Agda.Syntax.Abstract.Expr instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Internal.Sort Agda.Syntax.Abstract.Expr instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Internal.Level Agda.Syntax.Abstract.Expr instance (Agda.TypeChecking.Free.Free i, Agda.Syntax.Translation.InternalToAbstract.Reify i a) => Agda.Syntax.Translation.InternalToAbstract.Reify (Agda.Syntax.Internal.Abs i) (Agda.Syntax.Abstract.Name.Name, a) instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Internal.Telescope Agda.Syntax.Abstract.Telescope instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.Syntax.Internal.ArgInfo Agda.Syntax.Abstract.ArgInfo instance Agda.Syntax.Translation.InternalToAbstract.Reify i a => Agda.Syntax.Translation.InternalToAbstract.Reify (Agda.Syntax.Internal.Dom i) (Agda.Syntax.Abstract.Arg a) instance Agda.Syntax.Translation.InternalToAbstract.Reify i a => Agda.Syntax.Translation.InternalToAbstract.Reify [i] [a] instance (Agda.Syntax.Translation.InternalToAbstract.Reify i1 a1, Agda.Syntax.Translation.InternalToAbstract.Reify i2 a2) => Agda.Syntax.Translation.InternalToAbstract.Reify (i1, i2) (a1, a2) instance (Agda.Syntax.Translation.InternalToAbstract.Reify i1 a1, Agda.Syntax.Translation.InternalToAbstract.Reify i2 a2, Agda.Syntax.Translation.InternalToAbstract.Reify i3 a3) => Agda.Syntax.Translation.InternalToAbstract.Reify (i1, i2, i3) (a1, a2, a3) instance (Agda.Syntax.Translation.InternalToAbstract.Reify i1 a1, Agda.Syntax.Translation.InternalToAbstract.Reify i2 a2, Agda.Syntax.Translation.InternalToAbstract.Reify i3 a3, Agda.Syntax.Translation.InternalToAbstract.Reify i4 a4) => Agda.Syntax.Translation.InternalToAbstract.Reify (i1, i2, i3, i4) (a1, a2, a3, a4) module Agda.TypeChecking.Pretty type Doc = Doc comma :: TCM Doc colon :: TCM Doc equals :: TCM Doc pretty :: Pretty a => a -> TCM Doc prettyA :: (Pretty c, ToConcrete a c) => a -> TCM Doc prettyAs :: (Pretty c, ToConcrete a [c]) => a -> TCM Doc text :: String -> TCM Doc pwords :: String -> [TCM Doc] fwords :: String -> TCM Doc sep :: [TCM Doc] -> TCM Doc fsep :: [TCM Doc] -> TCM Doc hsep :: [TCM Doc] -> TCM Doc hcat :: [TCM Doc] -> TCM Doc vcat :: [TCM Doc] -> TCM Doc ($$) :: TCM Doc -> TCM Doc -> TCM Doc ($+$) :: TCM Doc -> TCM Doc -> TCM Doc (<>) :: TCM Doc -> TCM Doc -> TCM Doc (<+>) :: TCM Doc -> TCM Doc -> TCM Doc nest :: Int -> TCM Doc -> TCM Doc braces :: TCM Doc -> TCM Doc dbraces :: TCM Doc -> TCM Doc brackets :: TCM Doc -> TCM Doc parens :: TCM Doc -> TCM Doc -- | Comma-separated list in brackets. prettyList :: [TCM Doc] -> TCM Doc -- | prettyList without the brackets. prettyList_ :: [TCM Doc] -> TCM Doc punctuate :: TCM Doc -> [TCM Doc] -> [TCM Doc] class PrettyTCM a prettyTCM :: PrettyTCM a => a -> TCM Doc newtype PrettyContext PrettyContext :: Context -> PrettyContext -- | Show a pattern, given a method how to show pattern variables. showPat' :: (a -> TCM Doc) -> Pattern' a -> TCM Doc raisePatVars :: Int -> NLPat -> NLPat -- | Pairing something with a node (for printing only). data WithNode n a WithNode :: n -> a -> WithNode n a instance Agda.TypeChecking.Pretty.PrettyTCM GHC.Types.Bool instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Concrete.Name.Name instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Concrete.Name.QName instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.Comparison instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Literal.Literal instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Common.Nat instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.ProblemId instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Position.Range instance Agda.TypeChecking.Pretty.PrettyTCM a => Agda.TypeChecking.Pretty.PrettyTCM (Agda.TypeChecking.Monad.Base.Closure a) instance Agda.TypeChecking.Pretty.PrettyTCM a => Agda.TypeChecking.Pretty.PrettyTCM [a] instance (Agda.TypeChecking.Pretty.PrettyTCM a, Agda.TypeChecking.Pretty.PrettyTCM b) => Agda.TypeChecking.Pretty.PrettyTCM (a, b) instance (Agda.TypeChecking.Pretty.PrettyTCM a, Agda.TypeChecking.Pretty.PrettyTCM b, Agda.TypeChecking.Pretty.PrettyTCM c) => Agda.TypeChecking.Pretty.PrettyTCM (a, b, c) instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Internal.Term instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Internal.Type instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.DisplayTerm instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Translation.InternalToAbstract.NamedClause instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Internal.Level instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Utils.Permutation.Permutation instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.Polarity instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Internal.Clause instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Internal.ClauseBody instance Agda.TypeChecking.Pretty.PrettyTCM a => Agda.TypeChecking.Pretty.PrettyTCM (Agda.TypeChecking.Monad.Base.Judgement a) instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Common.MetaId instance Agda.TypeChecking.Pretty.PrettyTCM a => Agda.TypeChecking.Pretty.PrettyTCM (Agda.Syntax.Internal.Blocked a) instance (Agda.Syntax.Translation.InternalToAbstract.Reify a e, Agda.Syntax.Translation.AbstractToConcrete.ToConcrete e c, Agda.Utils.Pretty.Pretty c) => Agda.TypeChecking.Pretty.PrettyTCM (Agda.Syntax.Common.Named_ a) instance (Agda.Syntax.Translation.InternalToAbstract.Reify a e, Agda.Syntax.Translation.AbstractToConcrete.ToConcrete e c, Agda.Utils.Pretty.Pretty c) => Agda.TypeChecking.Pretty.PrettyTCM (Agda.Syntax.Internal.Arg a) instance (Agda.Syntax.Translation.InternalToAbstract.Reify a e, Agda.Syntax.Translation.AbstractToConcrete.ToConcrete e c, Agda.Utils.Pretty.Pretty c) => Agda.TypeChecking.Pretty.PrettyTCM (Agda.Syntax.Internal.Dom a) instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Internal.Elim instance Agda.TypeChecking.Pretty.PrettyTCM a => Agda.TypeChecking.Pretty.PrettyTCM (Agda.TypeChecking.Monad.Base.MaybeReduced a) instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Abstract.Expr instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Common.Relevance instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.ProblemConstraint instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.Constraint instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.TypeCheckingProblem instance Agda.TypeChecking.Pretty.PrettyTCM a => Agda.TypeChecking.Pretty.PrettyTCM (Agda.Syntax.Common.WithHiding a) instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Abstract.Name.Name instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Abstract.Name.QName instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Abstract.Name.ModuleName instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Internal.ConHead instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Internal.Telescope instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Pretty.PrettyContext instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.Context instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Internal.Pattern instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Syntax.Internal.DeBruijnPattern instance Agda.TypeChecking.Pretty.PrettyTCM (Agda.Syntax.Internal.Elim' Agda.TypeChecking.Monad.Base.DisplayTerm) instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.NLPat instance Agda.TypeChecking.Pretty.PrettyTCM (Agda.Syntax.Internal.Elim' Agda.TypeChecking.Monad.Base.NLPat) instance Agda.TypeChecking.Pretty.PrettyTCM (Agda.Syntax.Internal.Type' Agda.TypeChecking.Monad.Base.NLPat) instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.RewriteRule instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Positivity.Occurrence.Occurrence instance Agda.TypeChecking.Pretty.PrettyTCM n => Agda.TypeChecking.Pretty.PrettyTCM (Agda.TypeChecking.Pretty.WithNode n Agda.TypeChecking.Positivity.Occurrence.Occurrence) instance (Agda.TypeChecking.Pretty.PrettyTCM n, Agda.TypeChecking.Pretty.PrettyTCM (Agda.TypeChecking.Pretty.WithNode n e)) => Agda.TypeChecking.Pretty.PrettyTCM (Agda.Utils.Graph.AdjacencyMap.Unidirectional.Graph n n e) -- | Some arguments to functions (types in particular) will not be used in -- the body. Wouldn't it be useful if these wasn't passed around at all? -- Fear not, we here perform some analysis and try to remove as many of -- these occurences as possible. -- -- We employ the worker/wrapper transform, so if f x1 .. xn = e and we -- notice that some is not needed we create: f' xj .. xk = e [xi := unit] -- and f x1 .. xn = f' xj .. xk. i.e we erase them in f' and replace by -- unit, and the original f function calls the new f'. The idea is that f -- should be inlined and then peace on earth. module Agda.Compiler.Epic.Erasure isIrr :: Relevance -> Bool isRel :: Relevance -> Bool -- | Relevance "or" (||-) :: Relevance -> Relevance -> Relevance -- | Relevance "and" (&&-) :: Relevance -> Relevance -> Relevance data ErasureState ErasureState :: Map Var [Relevance] -> Map Var Fun -> ErasureState [relevancies] :: ErasureState -> Map Var [Relevance] [funs] :: ErasureState -> Map Var Fun type Erasure = StateT ErasureState -- | Try to find as many unused variables as possible erasure :: [Fun] -> Compile TCM [Fun] removeUnused :: Map Var [Relevance] -> Expr -> Expr -- | Initiate a function's relevancies initiate :: Fun -> Erasure (Compile TCM) () initialRels :: Type -> Relevance -> [Relevance] ignoreForced :: Relevance -> Bool -- | Calculate if a variable is relevant in an expression relevant :: (Functor m, Monad m) => Var -> Expr -> Erasure m Relevance -- | Try to find a fixpoint for all the functions relevance. step :: Integer -> Erasure (Compile TCM) (Map Var [Relevance]) diff :: (Ord k, Eq a) => Map k a -> Map k a -> [(k, (a, a))] module Agda.Compiler.Epic.Injection -- | Find potentially injective functions, solve constraints to fix some -- constructor tags and make functions whose constraints are fulfilled -- injections findInjection :: [(QName, Definition)] -> Compile TCM [(QName, Definition)] replaceFunCC :: QName -> CompiledClauses -> Compile TCM () -- | If the pairs of constructor names have the same tags, the function is -- injective. If Nothing, the function is not injective. type InjConstraints = Maybe [(QName, QName)] isInjective :: QName -> [Clause] -> Compile TCM (Maybe ((QName, InjectiveFun), [(QName, QName)])) patternToTerm :: Nat -> Pattern -> Term nrBinds :: Num i => Pattern -> i substForDot :: [NamedArg Pattern] -> Substitution isInjectiveHere :: QName -> Int -> Clause -> Compile TCM InjConstraints -- | Turn NATURAL literal n into suc^n zero. litToCon :: Literal -> TCM Term litInt :: Literal -> Bool insertAt :: (Nat, Term) -> Term -> Term solve :: [QName] -> [((QName, InjectiveFun), [(QName, QName)])] -> Compile TCM [(QName, InjectiveFun)] emptyC :: InjConstraints addConstraint :: QName -> QName -> InjConstraints -> InjConstraints unionConstraints :: [InjConstraints] -> InjConstraints -- | Are two terms injectible? Tries to find a mapping between constructors -- that equates the terms. -- -- Precondition: t1 is normalised, t2 is in WHNF When reducing t2, it may -- become a literal, which makes this not work in some cases... class Injectible a (<:) :: Injectible a => a -> a -> ReaderT (Map QName InjectiveFun) (Compile TCM) InjConstraints data TagEq Same :: Int -> TagEq IsTag :: Tag -> TagEq data Tags Tags :: IntMap (Set QName) -> Map QName TagEq -> Tags [eqGroups] :: Tags -> IntMap (Set QName) [constrGroup] :: Tags -> Map QName TagEq initialTags :: Map QName Tag -> [QName] -> Tags unify :: QName -> QName -> Tags -> Compile TCM (Maybe Tags) setTag :: Int -> Tag -> Tags -> Compile TCM (Maybe Tags) mergeGroups :: Int -> Int -> Tags -> Compile TCM (Maybe Tags) unifiable :: QName -> QName -> Compile TCM Bool (!!!!) :: Ord k => Map k v -> k -> v instance GHC.Classes.Eq Agda.Compiler.Epic.Injection.TagEq instance Agda.Compiler.Epic.Injection.Injectible a => Agda.Compiler.Epic.Injection.Injectible (Agda.Syntax.Internal.Arg a) instance Agda.Compiler.Epic.Injection.Injectible a => Agda.Compiler.Epic.Injection.Injectible [a] instance Agda.Compiler.Epic.Injection.Injectible a => Agda.Compiler.Epic.Injection.Injectible (Agda.Syntax.Internal.Elim' a) instance Agda.Compiler.Epic.Injection.Injectible Agda.Syntax.Internal.Term -- | Smash functions which return something that can be inferred (something -- of a type with only one element) module Agda.Compiler.Epic.Smashing defnPars :: Integral n => Defn -> n -- | Main function, smash as much as possible smash'em :: [Fun] -> Compile TCM [Fun] (+++) :: Telescope -> Telescope -> Telescope -- | Can a datatype be inferred? If so, return the only possible value. inferable :: Set QName -> QName -> [Arg Term] -> Compile TCM (Maybe Expr) inferableTerm :: Set QName -> Term -> Compile TCM (Maybe Expr) -- | Find the only possible value for a certain type. If we fail return -- Nothing smashable :: Int -> Type -> Compile TCM (Maybe Expr) buildLambda :: (Ord n, Num n) => n -> Expr -> Expr module Agda.TypeChecking.Rules.LHS.Problem type Substitution = [Maybe Term] type FlexibleVars = [FlexibleVar Nat] -- | When we encounter a flexible variable in the unifier, where did it -- come from? The alternatives are ordered such that we will assign the -- higher one first, i.e., first we try to assign a DotFlex, -- then... data FlexibleVarKind -- | From a record pattern (ConP). Saves the FlexibleVarKind -- of its subpatterns. RecordFlex :: [FlexibleVarKind] -> FlexibleVarKind -- | From a hidden formal argument or underscore (WildP). ImplicitFlex :: FlexibleVarKind -- | From a dot pattern (DotP). DotFlex :: FlexibleVarKind -- | Flexible variables are equipped with information where they come from, -- in order to make a choice which one to assign when two flexibles are -- unified. data FlexibleVar a FlexibleVar :: Hiding -> FlexibleVarKind -> a -> FlexibleVar a [flexHiding] :: FlexibleVar a -> Hiding [flexKind] :: FlexibleVar a -> FlexibleVarKind [flexVar] :: FlexibleVar a -> a defaultFlexibleVar :: a -> FlexibleVar a flexibleVarFromHiding :: Hiding -> a -> FlexibleVar a -- | State of typechecking a LHS; input to split. [Ulf Norell's -- PhD, page. 35] -- -- In Problem ps p delta, ps are the user patterns of -- supposed type delta. p is the pattern resulting from -- the splitting. data Problem' p Problem :: [NamedArg Pattern] -> p -> Telescope -> ProblemRest -> Problem' p -- | User patterns. [problemInPat] :: Problem' p -> [NamedArg Pattern] -- | Patterns after splitting. [problemOutPat] :: Problem' p -> p -- | Type of patterns. [problemTel] :: Problem' p -> Telescope -- | Patterns that cannot be typed yet. [problemRest] :: Problem' p -> ProblemRest -- | The permutation should permute allHoles of the patterns to -- correspond to the abstract patterns in the problem. type Problem = Problem' (Permutation, [NamedArg Pattern]) type ProblemPart = Problem' () -- | User patterns that could not be given a type yet. -- -- Example: f : (b : Bool) -> if b then Nat else Nat -> Nat f -- true = zero f false zero = zero f false (suc n) = n In this -- sitation, for clause 2, we construct an initial problem -- problemInPat = [false] problemTel = (b : Bool) problemRest.restPats = -- [zero] problemRest.restType = if b then Nat else Nat -> Nat -- As we instantiate b to false, the restType -- reduces to Nat -> Nat and we can move pattern -- zero over to problemInPat. data ProblemRest ProblemRest :: [NamedArg Pattern] -> Arg Type -> ProblemRest -- | List of user patterns which could not yet be typed. [restPats] :: ProblemRest -> [NamedArg Pattern] -- | Type eliminated by restPats. Can be Irrelevant to -- indicate that we came by an irrelevant projection and, hence, the rhs -- must be type-checked in irrelevant mode. [restType] :: ProblemRest -> Arg Type data Focus Focus :: QName -> ConPOrigin -> [NamedArg Pattern] -> Range -> OneHolePatterns -> Int -> QName -> [Arg Term] -> [Arg Term] -> Type -> Focus [focusCon] :: Focus -> QName -- | Do we come from an implicit or record pattern? [focusPatOrigin] :: Focus -> ConPOrigin [focusConArgs] :: Focus -> [NamedArg Pattern] [focusRange] :: Focus -> Range [focusOutPat] :: Focus -> OneHolePatterns -- | Index of focused variable in the out patterns. [focusHoleIx] :: Focus -> Int [focusDatatype] :: Focus -> QName [focusParams] :: Focus -> [Arg Term] [focusIndices] :: Focus -> [Arg Term] -- | Type of variable we are splitting, kept for record patterns. [focusType] :: Focus -> Type LitFocus :: Literal -> OneHolePatterns -> Int -> Type -> Focus -- | Result of splitProblem: Determines position for the next -- split. data SplitProblem -- | Split on constructor pattern. Split :: ProblemPart -> [Name] -> Arg Focus -> Abs ProblemPart -> SplitProblem -- | The typed user patterns left of the split position. Invariant: -- problemRest == empty. [splitLPats] :: SplitProblem -> ProblemPart -- | The as-bindings for the focus. [splitAsNames] :: SplitProblem -> [Name] -- | How to split the variable at the split position. [splitFocus] :: SplitProblem -> Arg Focus -- | The typed user patterns right of the split position. [splitRPats] :: SplitProblem -> Abs ProblemPart -- | Split on projection pattern. SplitRest :: Arg QName -> Type -> SplitProblem -- | The projection could be belonging to an irrelevant record field. [splitProjection] :: SplitProblem -> Arg QName [splitRestType] :: SplitProblem -> Type -- | Put a typed pattern on the very left of a SplitProblem. consSplitProblem :: NamedArg Pattern -> ArgName -> Dom Type -> SplitProblem -> SplitProblem data DotPatternInst DPI :: Expr -> Term -> (Dom Type) -> DotPatternInst data AsBinding AsB :: Name -> Term -> Type -> AsBinding -- | State worked on during the main loop of checking a lhs. data LHSState LHSState :: Problem -> Substitution -> [DotPatternInst] -> [AsBinding] -> LHSState [lhsProblem] :: LHSState -> Problem [lhsSubst] :: LHSState -> Substitution [lhsDPI] :: LHSState -> [DotPatternInst] [lhsAsB] :: LHSState -> [AsBinding] instance GHC.Show.Show p => GHC.Show.Show (Agda.TypeChecking.Rules.LHS.Problem.Problem' p) instance GHC.Show.Show Agda.TypeChecking.Rules.LHS.Problem.ProblemRest instance Data.Traversable.Traversable Agda.TypeChecking.Rules.LHS.Problem.FlexibleVar instance Data.Foldable.Foldable Agda.TypeChecking.Rules.LHS.Problem.FlexibleVar instance GHC.Base.Functor Agda.TypeChecking.Rules.LHS.Problem.FlexibleVar instance GHC.Show.Show a => GHC.Show.Show (Agda.TypeChecking.Rules.LHS.Problem.FlexibleVar a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.TypeChecking.Rules.LHS.Problem.FlexibleVar a) instance GHC.Show.Show Agda.TypeChecking.Rules.LHS.Problem.FlexibleVarKind instance GHC.Classes.Ord Agda.TypeChecking.Rules.LHS.Problem.FlexibleVarKind instance GHC.Classes.Eq Agda.TypeChecking.Rules.LHS.Problem.FlexibleVarKind instance Agda.Syntax.Common.LensHiding (Agda.TypeChecking.Rules.LHS.Problem.FlexibleVar a) instance GHC.Classes.Ord (Agda.TypeChecking.Rules.LHS.Problem.FlexibleVar Agda.Syntax.Common.Nat) instance Agda.TypeChecking.Substitute.Subst Agda.TypeChecking.Rules.LHS.Problem.ProblemRest instance Agda.TypeChecking.Substitute.Subst (Agda.TypeChecking.Rules.LHS.Problem.Problem' p) instance Agda.TypeChecking.Substitute.Subst Agda.TypeChecking.Rules.LHS.Problem.DotPatternInst instance Agda.TypeChecking.Substitute.Subst Agda.TypeChecking.Rules.LHS.Problem.AsBinding instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Rules.LHS.Problem.DotPatternInst instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Rules.LHS.Problem.AsBinding instance Agda.Utils.Null.Null Agda.TypeChecking.Rules.LHS.Problem.ProblemRest instance Agda.Utils.Null.Null a => Agda.Utils.Null.Null (Agda.TypeChecking.Rules.LHS.Problem.Problem' a) -- | Find the places where the builtin static is used and do some -- normalisation there. module Agda.Compiler.Epic.Static normaliseStatic :: CompiledClauses -> Compile TCM CompiledClauses evaluateCC :: CompiledClauses -> Compile TCM CompiledClauses etaExpand :: Term -> Compile TCM Term class Evaluate a evaluate :: Evaluate a => a -> Compile TCM a instance Agda.Compiler.Epic.Static.Evaluate a => Agda.Compiler.Epic.Static.Evaluate [a] instance Agda.Compiler.Epic.Static.Evaluate a => Agda.Compiler.Epic.Static.Evaluate (Agda.Syntax.Internal.Arg a) instance Agda.Compiler.Epic.Static.Evaluate a => Agda.Compiler.Epic.Static.Evaluate (Agda.Syntax.Internal.Abs a) instance Agda.Compiler.Epic.Static.Evaluate a => Agda.Compiler.Epic.Static.Evaluate (Agda.Syntax.Internal.Elim' a) instance Agda.Compiler.Epic.Static.Evaluate Agda.Syntax.Internal.Term -- | Convert from Agda's internal representation to our auxiliary AST. module Agda.Compiler.Epic.FromAgda -- | Convert from Agda's internal representation to our auxiliary AST. fromAgda :: Maybe Term -> [(QName, Definition)] -> Compile TCM [Fun] -- | Translate an Agda definition to an Epic function where applicable translateDefn :: Maybe Term -> (QName, Definition) -> Compile TCM (Maybe Fun) reverseCCBody :: Int -> CompiledClauses -> CompiledClauses -- | Translate from Agda's desugared pattern matching (CompiledClauses) to -- our AuxAST. This is all done by magic. It uses substTerm to -- translate the actual terms when the cases have been gone through. The -- case expressions that we get use de Bruijn indices that change after -- each case in the following way. Say we have this pattern: -- --
--   f (X x y) (Y z) = term
--   
-- -- Initially, the variables have these indexes: -- --
--   f 0@(X x y) 1@(Y z) = term
--   
-- -- The first case will be on 0, and the variables bound inside -- the X pattern will replace the outer index, so we get -- something like this: -- --
--   f 0 2@(Y z) = case 0 of X 0 1 -> term
--   
-- -- Notice how (Y z) now has index 2. Then the second -- pattern is desugared in the same way: -- --
--   f 0 2 = case 0 of X 0 1 -> case 2 of Y 2 -> term
--   
-- -- This replacement is what is done using the replaceAt function. -- -- CompiledClauses also have default branches for when all branches fail -- (even inner branches), the catchAllBranch. Epic does not support this, -- so we have to add the catchAllBranch to each inner case (here we are -- calling it omniDefault). To avoid code duplication it is first bound -- by a let expression. compileClauses :: QName -> Int -> CompiledClauses -> Compile TCM Fun -- | Translate the actual Agda terms, with an environment of all the bound -- variables from patternmatching. Agda terms are in de Bruijn so we just -- check the new names in the position. substTerm :: [Var] -> Term -> Compile TCM Expr -- | Translate Agda literals to our AUX definition substLit :: Literal -> Compile TCM Lit -- | Translating Agda types to Haskell types. Used to ensure that imported -- Haskell functions have the right type. module Agda.Compiler.HaskellTypes type HaskellKind = String hsStar :: HaskellKind hsKFun :: HaskellKind -> HaskellKind -> HaskellKind hsFun :: HaskellKind -> HaskellKind -> HaskellKind hsUnit :: HaskellType hsVar :: Name -> HaskellType hsApp :: String -> [HaskellType] -> HaskellType hsForall :: String -> HaskellType -> HaskellType notAHaskellKind :: Type -> TCM a notAHaskellType :: Type -> TCM a getHsType :: QName -> TCM HaskellType getHsVar :: Nat -> TCM HaskellCode isHaskellKind :: Type -> TCM Bool haskellKind :: Type -> TCM HaskellKind -- | Note that Inf a b, where Inf is the INFINITY -- builtin, is translated to of b (assuming that all -- coinductive builtins are defined). -- -- Note that if haskellType supported universe polymorphism then -- the special treatment of INFINITY might not be needed. haskellType :: Type -> TCM HaskellType module Agda.Compiler.MAlonzo.Primitives -- | Check that the main function has type IO a, for some a. checkTypeOfMain :: QName -> Type -> TCM [Decl] -> TCM [Decl] importsForPrim :: TCM [ModuleName] declsForPrim :: TCM [Decl] mazNatToInteger :: String mazIntegerToNat :: String mazNatToInt :: String mazIntToNat :: String mazCharToInteger :: String mazListToHList :: String mazHListToList :: String mazListToString :: String mazStringToList :: String mazBoolToHBool :: String mazHBoolToBool :: String xForPrim :: [(String, TCM [a])] -> TCM [a] primBody :: String -> TCM Exp repl :: [String] -> String -> String pconName :: String -> TCM String hasCompiledData :: [String] -> TCM Bool bltQual' :: String -> String -> TCM String module Agda.TypeChecking.Records -- | Order the fields of a record construction. Use the second argument for -- missing fields. orderFields :: QName -> a -> [Name] -> [(Name, a)] -> TCM [a] -- | The name of the module corresponding to a record. recordModule :: QName -> ModuleName -- | Get the definition for a record. Throws an exception if the name does -- not refer to a record or the record is abstract. getRecordDef :: QName -> TCM Defn -- | Get the record name belonging to a field name. getRecordOfField :: QName -> TCM (Maybe QName) -- | Get the field names of a record. getRecordFieldNames :: QName -> TCM [Arg Name] recordFieldNames :: Defn -> [Arg Name] -- | Find all records with at least the given fields. findPossibleRecords :: [Name] -> TCM [QName] -- | Get the field types of a record. getRecordFieldTypes :: QName -> TCM Telescope -- | Get the field names belonging to a record type. getRecordTypeFields :: Type -> TCM [Arg QName] -- | Get the original name of the projection (the current one could be from -- a module application). getOriginalProjection :: QName -> TCM QName -- | Get the type of the record constructor. getRecordConstructorType :: QName -> TCM Type -- | Returns the given record type's constructor name (with an empty -- range). getRecordConstructor :: QName -> TCM ConHead -- | Check if a name refers to a record. If yes, return record definition. isRecord :: HasConstInfo m => QName -> m (Maybe Defn) -- | Reduce a type and check whether it is a record type. Succeeds only if -- type is not blocked by a meta var. If yes, return its name, -- parameters, and definition. isRecordType :: Type -> TCM (Maybe (QName, Args, Defn)) -- | Reduce a type and check whether it is a record type. Succeeds only if -- type is not blocked by a meta var. If yes, return its name, -- parameters, and definition. If no, return the reduced type (unless it -- is blocked). tryRecordType :: Type -> TCM (Either (Maybe Type) (QName, Args, Defn)) -- | The analogue of piApply. If v is a value of record -- type t with field f, then projectTyped v t -- f returns the type of f v. -- -- Works also for projection-like definitions f. -- -- Precondition: t is reduced. projectTyped :: Term -> Type -> QName -> TCM (Maybe (Term, Type)) -- | Check if a name refers to an eta expandable record. isEtaRecord :: HasConstInfo m => QName -> m Bool isEtaCon :: HasConstInfo m => QName -> m Bool -- | Check if a name refers to a record which is not coinductive. -- (Projections are then size-preserving) isInductiveRecord :: QName -> TCM Bool -- | Check if a type is an eta expandable record and return the record -- identifier and the parameters. isEtaRecordType :: Type -> TCM (Maybe (QName, Args)) -- | Check if a name refers to a record constructor. If yes, return record -- definition. isRecordConstructor :: MonadTCM tcm => QName -> tcm (Maybe (QName, Defn)) -- | Check if a constructor name is the internally generated record -- constructor. isGeneratedRecordConstructor :: QName -> TCM Bool -- | Mark record type as unguarded. No eta-expansion. Projections do not -- preserve guardedness. unguardedRecord :: QName -> TCM () -- | Mark record type as recursive. Projections do not preserve -- guardedness. recursiveRecord :: QName -> TCM () -- | Check whether record type is marked as recursive. -- -- Precondition: record type identifier exists in signature. isRecursiveRecord :: QName -> TCM Bool -- | Version of recRecursive with proper internal error. recRecursive_ :: Defn -> Bool -- |
--   etaExpandBoundVar i = (Δ, σ, τ)
--   
-- -- Precondition: The current context is Γ = Γ₁, x:R pars, Γ₂ -- where |Γ₂| = i and R is a eta-expandable record type -- with constructor c and fields Γ'. -- -- Postcondition: Δ = Γ₁, Γ', Γ₂[c Γ'] and Γ ⊢ σ : Δ -- and Δ ⊢ τ : Γ. etaExpandBoundVar :: Int -> TCM (Maybe (Telescope, Substitution, Substitution)) -- |
--   expandRecordVar i Γ = (Δ, σ, τ, Γ')
--   
-- -- Precondition: Γ = Γ₁, x:R pars, Γ₂ where |Γ₂| = i -- and R is a eta-expandable record type with constructor -- c and fields Γ'. -- -- Postcondition: Δ = Γ₁, Γ', Γ₂[c Γ'] and Γ ⊢ σ : Δ -- and Δ ⊢ τ : Γ. expandRecordVar :: Int -> Telescope -> TCM (Maybe (Telescope, Substitution, Substitution, Telescope)) -- | Precondition: variable list is ordered descendingly. Can be empty. expandRecordVarsRecursively :: [Int] -> Telescope -> TCM (Telescope, Substitution, Substitution) -- |
--   curryAt v (Γ (y : R pars) -> B) n =
--        (  v -> λ Γ ys → v Γ (c ys)            {- curry   -}
--        ,  v -> λ Γ y → v Γ (p1 y) ... (pm y)  {- uncurry -}
--        , Γ (ys : As) → B[c ys / y]
--        )
--   
-- -- where n = size Γ. curryAt :: Type -> Int -> TCM (Term -> Term, Term -> Term, Type) -- | etaExpand r pars u computes the eta expansion of record value -- u at record type r pars. -- -- The first argument r should be the name of a record type. -- Given -- --
--   record R : Set where field x : A; y : B; .z : C
--   
-- -- and r : R, -- --
--   etaExpand R [] r = (tel, [R.x r, R.y r, R.z r])
--   
-- -- where tel is the record telescope instantiated at the -- parameters pars. etaExpandRecord :: QName -> Args -> Term -> TCM (Telescope, Args) etaExpandRecord_ :: QName -> Args -> Defn -> Term -> TCM (Telescope, ConHead, Args) etaExpandAtRecordType :: Type -> Term -> TCM (Telescope, Term) -- | The fields should be eta contracted already. -- -- We can eta contract if all fields f = ... are irrelevant or -- all fields f are the projection f v of the same -- value v, but we need at least one relevant field to find the -- value v. -- -- TODO: this can be moved out of TCM (but only if ConHead stores also -- the Arg-decoration of the record fields. etaContractRecord :: HasConstInfo m => QName -> ConHead -> Args -> m Term -- | Is the type a hereditarily singleton record type? May return a -- blocking metavariable. -- -- Precondition: The name should refer to a record type, and the -- arguments should be the parameters to the type. isSingletonRecord :: QName -> Args -> TCM (Either MetaId Bool) isSingletonRecordModuloRelevance :: QName -> Args -> TCM (Either MetaId Bool) -- | Return the unique (closed) inhabitant if exists. In case of counting -- irrelevance in, the returned inhabitant contains garbage. isSingletonRecord' :: Bool -> QName -> Args -> TCM (Either MetaId (Maybe Term)) -- | Check whether a type has a unique inhabitant and return it. Can be -- blocked by a metavar. isSingletonType :: Type -> TCM (Either MetaId (Maybe Term)) -- | Check whether a type has a unique inhabitant (irrelevant parts -- ignored). Can be blocked by a metavar. isSingletonTypeModuloRelevance :: (MonadTCM tcm) => Type -> tcm (Either MetaId Bool) isSingletonType' :: Bool -> Type -> TCM (Either MetaId (Maybe Term)) -- | Auxiliary function. emap :: (a -> b) -> Either c (Maybe a) -> Either c (Maybe b) -- | Translation from Agda.Syntax.Concrete to -- Agda.Syntax.Abstract. Involves scope analysis, figuring out -- infix operator precedences and tidying up definitions. module Agda.Syntax.Translation.ConcreteToAbstract -- | Things that can be translated to abstract syntax are instances of this -- class. class ToAbstract concrete abstract | concrete -> abstract toAbstract :: ToAbstract concrete abstract => concrete -> ScopeM abstract -- | This operation does not affect the scope, i.e. the original scope is -- restored upon completion. localToAbstract :: ToAbstract c a => c -> (a -> ScopeM b) -> ScopeM b concreteToAbstract_ :: ToAbstract c a => c -> ScopeM a concreteToAbstract :: ToAbstract c a => ScopeInfo -> c -> ScopeM a newtype NewModuleQName NewModuleQName :: QName -> NewModuleQName newtype OldName OldName :: Name -> OldName -- | Temporary data type to scope check a file. data TopLevel a TopLevel :: AbsolutePath -> a -> TopLevel a -- | The file path from which we loaded this module. [topLevelPath] :: TopLevel a -> AbsolutePath -- | The file content. [topLevelTheThing] :: TopLevel a -> a data TopLevelInfo TopLevelInfo :: [Declaration] -> ScopeInfo -> ScopeInfo -> TopLevelInfo [topLevelDecls] :: TopLevelInfo -> [Declaration] [outsideScope] :: TopLevelInfo -> ScopeInfo [insideScope] :: TopLevelInfo -> ScopeInfo -- | The top-level module name. topLevelModuleName :: TopLevelInfo -> ModuleName data AbstractRHS data NewModuleName data OldModuleName data NewName a data OldQName data LeftHandSide data RightHandSide data PatName data APatName data LetDef data LetDefs instance (Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract c1 a1, Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract c2 a2) => Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (c1, c2) (a1, a2) instance (Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract c1 a1, Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract c2 a2, Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract c3 a3) => Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (c1, c2, c3) (a1, a2, a3) instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract c a => Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract [c] [a] instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract c a => Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (GHC.Base.Maybe c) (GHC.Base.Maybe a) instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (Agda.Syntax.Translation.ConcreteToAbstract.NewName Agda.Syntax.Concrete.Name.Name) Agda.Syntax.Abstract.Name.Name instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (Agda.Syntax.Translation.ConcreteToAbstract.NewName Agda.Syntax.Concrete.BoundName) Agda.Syntax.Abstract.Name.Name instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.OldQName Agda.Syntax.Abstract.Expr instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.PatName Agda.Syntax.Translation.ConcreteToAbstract.APatName instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.OldName Agda.Syntax.Abstract.Name.QName instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.NewModuleName Agda.Syntax.Abstract.Name.ModuleName instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.NewModuleQName Agda.Syntax.Abstract.Name.ModuleName instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.OldModuleName Agda.Syntax.Abstract.Name.ModuleName instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Concrete.Expr Agda.Syntax.Abstract.Expr instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Concrete.LamBinding Agda.Syntax.Abstract.LamBinding instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Concrete.TypedBindings Agda.Syntax.Abstract.TypedBindings instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Concrete.TypedBinding Agda.Syntax.Abstract.TypedBinding instance Agda.Syntax.Translation.ConcreteToAbstract.EnsureNoLetStms Agda.Syntax.Concrete.TypedBinding instance Agda.Syntax.Translation.ConcreteToAbstract.EnsureNoLetStms a => Agda.Syntax.Translation.ConcreteToAbstract.EnsureNoLetStms (Agda.Syntax.Concrete.LamBinding' a) instance Agda.Syntax.Translation.ConcreteToAbstract.EnsureNoLetStms a => Agda.Syntax.Translation.ConcreteToAbstract.EnsureNoLetStms (Agda.Syntax.Concrete.TypedBindings' a) instance Agda.Syntax.Translation.ConcreteToAbstract.EnsureNoLetStms a => Agda.Syntax.Translation.ConcreteToAbstract.EnsureNoLetStms [a] instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (Agda.Syntax.Translation.ConcreteToAbstract.TopLevel [Agda.Syntax.Concrete.Declaration]) Agda.Syntax.Translation.ConcreteToAbstract.TopLevelInfo instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract [Agda.Syntax.Concrete.Declaration] [Agda.Syntax.Abstract.Declaration] instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.LetDefs [Agda.Syntax.Abstract.LetBinding] instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.LetDef [Agda.Syntax.Abstract.LetBinding] instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (Agda.Syntax.Translation.ConcreteToAbstract.Blind a) (Agda.Syntax.Translation.ConcreteToAbstract.Blind a) instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Concrete.Definitions.NiceDeclaration Agda.Syntax.Abstract.Declaration instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.ConstrDecl Agda.Syntax.Abstract.Declaration instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Concrete.Pragma [Agda.Syntax.Abstract.Pragma] instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Concrete.Definitions.Clause Agda.Syntax.Abstract.Clause instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.AbstractRHS Agda.Syntax.Abstract.RHS instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.RightHandSide Agda.Syntax.Translation.ConcreteToAbstract.AbstractRHS instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Concrete.RHS Agda.Syntax.Translation.ConcreteToAbstract.AbstractRHS instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Translation.ConcreteToAbstract.LeftHandSide Agda.Syntax.Abstract.LHS instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Concrete.LHSCore (Agda.Syntax.Abstract.LHSCore' Agda.Syntax.Concrete.Expr) instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract c a => Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (Agda.Syntax.Common.WithHiding c) (Agda.Syntax.Common.WithHiding a) instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract c a => Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (Agda.Syntax.Concrete.Arg c) (Agda.Syntax.Abstract.Arg a) instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract c a => Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (Agda.Syntax.Common.Named name c) (Agda.Syntax.Common.Named name a) instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (Agda.Syntax.Abstract.LHSCore' Agda.Syntax.Concrete.Expr) (Agda.Syntax.Abstract.LHSCore' Agda.Syntax.Abstract.Expr) instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract c a => Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (Agda.Syntax.Abstract.NamedArg c) (Agda.Syntax.Abstract.NamedArg a) instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Concrete.ArgInfo Agda.Syntax.Abstract.ArgInfo instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract (Agda.Syntax.Abstract.Pattern' Agda.Syntax.Concrete.Expr) (Agda.Syntax.Abstract.Pattern' Agda.Syntax.Abstract.Expr) instance Agda.Syntax.Translation.ConcreteToAbstract.ToAbstract Agda.Syntax.Concrete.Pattern (Agda.Syntax.Abstract.Pattern' Agda.Syntax.Concrete.Expr) -- | The monad for the termination checker. -- -- The termination monad TerM is an extension of the type -- checking monad TCM by an environment with information needed by -- the termination checker. module Agda.Termination.Monad -- | The mutual block we are checking. -- -- The functions are numbered according to their order of appearance in -- this list. type MutualNames = [QName] -- | The target of the function we are checking. type Target = QName -- | The current guardedness level. type Guarded = Order -- | The termination environment. data TerEnv TerEnv :: Bool -> Bool -> Bool -> Maybe QName -> Maybe QName -> CutOff -> QName -> MutualNames -> [QName] -> Maybe Target -> Delayed -> [Bool] -> Bool -> Int -> MaskedDeBruijnPats -> !Int -> !Guarded -> Bool -> VarSet -> TerEnv -- | Are we mining dot patterns to find evindence of structal descent? [terUseDotPatterns] :: TerEnv -> Bool -- | Do we assume that record and data type constructors preserve -- guardedness? [terGuardingTypeConstructors] :: TerEnv -> Bool -- | Do we inline with functions to enhance termination checking of with? [terInlineWithFunctions] :: TerEnv -> Bool -- | The name of size successor, if any. [terSizeSuc] :: TerEnv -> Maybe QName -- | The name of the delay constructor (sharp), if any. [terSharp] :: TerEnv -> Maybe QName -- | Depth at which to cut off the structural order. [terCutOff] :: TerEnv -> CutOff -- | The name of the function we are currently checking. [terCurrent] :: TerEnv -> QName -- | The names of the functions in the mutual block we are checking. This -- includes the internally generated functions (with, extendedlambda, -- coinduction). [terMutual] :: TerEnv -> MutualNames -- | The list of name actually appearing in the file (abstract syntax). -- Excludes the internally generated functions. [terUserNames] :: TerEnv -> [QName] -- | Target type of the function we are currently termination checking. -- Only the constructors of Target are considered guarding. [terTarget] :: TerEnv -> Maybe Target -- | Are we checking a delayed definition? [terDelayed] :: TerEnv -> Delayed -- | Only consider the notMasked False arguments for -- establishing termination. [terMaskArgs] :: TerEnv -> [Bool] -- | Only consider guardedness if False (not masked). [terMaskResult] :: TerEnv -> Bool -- | How many SIZELT relations do we have in the context (= clause -- telescope). Used to approximate termination for metas in call args. [_terSizeDepth] :: TerEnv -> Int -- | The patterns of the clause we are checking. [terPatterns] :: TerEnv -> MaskedDeBruijnPats -- | Number of additional binders we have gone under (and consequently need -- to raise the patterns to compare to terms). Updated during call graph -- extraction, hence strict. [terPatternsRaise] :: TerEnv -> !Int -- | The current guardedness status. Changes as we go deeper into the term. -- Updated during call graph extraction, hence strict. [terGuarded] :: TerEnv -> !Guarded -- | When extracting usable size variables during construction of the call -- matrix, can we take the variable for use with SIZELT constraints from -- the context? Yes, if we are under an inductive constructor. No, if we -- are under a record constructor. [terUseSizeLt] :: TerEnv -> Bool -- | Pattern variables that can be compared to argument variables using -- SIZELT. [terUsableVars] :: TerEnv -> VarSet -- | An empty termination environment. -- -- Values are set to a safe default meaning that with these initial -- values the termination checker will not miss termination errors it -- would have seen with better settings of these values. -- -- Values that do not have a safe default are set to IMPOSSIBLE. defaultTerEnv :: TerEnv -- | Termination monad service class. class (Functor m, Monad m) => MonadTer m where terAsks f = f <$> terAsk terAsk :: MonadTer m => m TerEnv terLocal :: MonadTer m => (TerEnv -> TerEnv) -> m a -> m a terAsks :: MonadTer m => (TerEnv -> a) -> m a -- | Termination monad. newtype TerM a TerM :: ReaderT TerEnv TCM a -> TerM a [terM] :: TerM a -> ReaderT TerEnv TCM a -- | Generic run method for termination monad. runTer :: TerEnv -> TerM a -> TCM a -- | Run TerM computation in default environment (created from options). runTerDefault :: TerM a -> TCM a terGetGuardingTypeConstructors :: TerM Bool terGetInlineWithFunctions :: TerM Bool terGetUseDotPatterns :: TerM Bool terSetUseDotPatterns :: Bool -> TerM a -> TerM a terGetSizeSuc :: TerM (Maybe QName) terGetCurrent :: TerM QName terSetCurrent :: QName -> TerM a -> TerM a terGetSharp :: TerM (Maybe QName) terGetCutOff :: TerM CutOff terGetMutual :: TerM MutualNames terGetUserNames :: TerM [QName] terGetTarget :: TerM (Maybe Target) terSetTarget :: Maybe Target -> TerM a -> TerM a terGetDelayed :: TerM Delayed terSetDelayed :: Delayed -> TerM a -> TerM a terGetMaskArgs :: TerM [Bool] terSetMaskArgs :: [Bool] -> TerM a -> TerM a terGetMaskResult :: TerM Bool terSetMaskResult :: Bool -> TerM a -> TerM a terGetPatterns :: TerM (MaskedDeBruijnPats) terSetPatterns :: MaskedDeBruijnPats -> TerM a -> TerM a terRaise :: TerM a -> TerM a terGetGuarded :: TerM Guarded terModifyGuarded :: (Order -> Order) -> TerM a -> TerM a terSetGuarded :: Order -> TerM a -> TerM a terUnguarded :: TerM a -> TerM a -- | Should the codomain part of a function type preserve guardedness? terPiGuarded :: TerM a -> TerM a -- | Lens for _terSizeDepth. terSizeDepth :: Lens' Int TerEnv -- | Lens for terUsableVars. terGetUsableVars :: TerM VarSet terModifyUsableVars :: (VarSet -> VarSet) -> TerM a -> TerM a terSetUsableVars :: VarSet -> TerM a -> TerM a -- | Lens for terUseSizeLt. terGetUseSizeLt :: TerM Bool terModifyUseSizeLt :: (Bool -> Bool) -> TerM a -> TerM a terSetUseSizeLt :: Bool -> TerM a -> TerM a -- | Compute usable vars from patterns and run subcomputation. withUsableVars :: UsableSizeVars a => a -> TerM b -> TerM b -- | Set terUseSizeLt when going under constructor c. conUseSizeLt :: QName -> TerM a -> TerM a -- | Set terUseSizeLt for arguments following projection q. -- We disregard j<i after a non-coinductive projection. However, the -- projection need not be recursive (Issue 1470). projUseSizeLt :: QName -> TerM a -> TerM a -- | For termination checking purposes flat should not be considered a -- projection. That is, it flat doesn't preserve either structural order -- or guardedness like other projections do. Andreas, 2012-06-09: the -- same applies to projections of recursive records. isProjectionButNotCoinductive :: MonadTCM tcm => QName -> tcm Bool -- | Check whether a projection belongs to a coinductive record and is -- actually recursive. E.g. @ isCoinductiveProjection (Stream.head) = -- return False -- -- isCoinductiveProjection (Stream.tail) = return True @ isCoinductiveProjection :: MonadTCM tcm => Bool -> QName -> tcm Bool type DeBruijnPats = [DeBruijnPat] -- | Patterns with variables as de Bruijn indices. type DeBruijnPat = DeBruijnPat' Int data DeBruijnPat' a -- | De Bruijn Index. VarDBP :: a -> DeBruijnPat' a -- | The name refers to either an ordinary constructor or the successor -- function on sized types. ConDBP :: QName -> [DeBruijnPat' a] -> DeBruijnPat' a -- | Literal. Also abused to censor part of a pattern. LitDBP :: Literal -> DeBruijnPat' a -- | Part of dot pattern that cannot be converted into a pattern. TermDBP :: Term -> DeBruijnPat' a -- | Projection pattern. ProjDBP :: QName -> DeBruijnPat' a -- | How long is the path to the deepest variable? patternDepth :: DeBruijnPat' a -> Int -- | A dummy pattern used to mask a pattern that cannot be used for -- structural descent. unusedVar :: DeBruijnPat -- | raiseDBP n ps increases each de Bruijn index in ps -- by n. Needed when going under a binder during analysis of a -- term. raiseDBP :: Int -> DeBruijnPats -> DeBruijnPats -- | Extract variables from DeBruijnPats that could witness a -- decrease via a SIZELT constraint. -- -- These variables must be under an inductive constructor (with no record -- constructor in the way), or after a coinductive projection (with no -- inductive one in the way). class UsableSizeVars a usableSizeVars :: UsableSizeVars a => a -> TerM VarSet type MaskedDeBruijnPats = [Masked DeBruijnPat] data Masked a Masked :: Bool -> a -> Masked a -- | True if thing not eligible for structural descent. [getMask] :: Masked a -> Bool -- | Thing. [getMasked] :: Masked a -> a masked :: a -> Masked a notMasked :: a -> Masked a -- | Print masked things in double parentheses. -- | The call information is stored as free monoid over CallInfo. As -- long as we never look at it, only accumulate it, it does not matter -- whether we use Set, (nub) list, or Tree. Internally, -- due to lazyness, it is anyway a binary tree of mappend nodes -- and singleton leafs. Since we define no order on CallInfo -- (expensive), we cannot use a Set or nub list. -- Performance-wise, I could not see a difference between Set and list. newtype CallPath CallPath :: [CallInfo] -> CallPath [callInfos] :: CallPath -> [CallInfo] -- | Only show intermediate nodes. (Drop last CallInfo). -- | A very crude way of estimating the SIZELT chains i > j -- > k in context. Returns 3 in this case. Overapproximates. terSetSizeDepth :: Telescope -> TerM a -> TerM a instance Agda.Syntax.Abstract.AllNames Agda.Termination.Monad.CallPath instance GHC.Base.Monoid Agda.Termination.Monad.CallPath instance GHC.Show.Show Agda.Termination.Monad.CallPath instance Agda.Utils.Benchmark.MonadBench Agda.Benchmarking.Phase Agda.Termination.Monad.TerM instance GHC.Base.Monad Agda.Termination.Monad.TerM instance GHC.Base.Applicative Agda.Termination.Monad.TerM instance GHC.Base.Functor Agda.Termination.Monad.TerM instance Data.Traversable.Traversable Agda.Termination.Monad.Masked instance Data.Foldable.Foldable Agda.Termination.Monad.Masked instance GHC.Base.Functor Agda.Termination.Monad.Masked instance GHC.Show.Show a => GHC.Show.Show (Agda.Termination.Monad.Masked a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.Termination.Monad.Masked a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.Termination.Monad.Masked a) instance GHC.Show.Show a => GHC.Show.Show (Agda.Termination.Monad.DeBruijnPat' a) instance GHC.Base.Functor Agda.Termination.Monad.DeBruijnPat' instance Agda.Termination.Monad.MonadTer Agda.Termination.Monad.TerM instance Control.Monad.Reader.Class.MonadReader Agda.TypeChecking.Monad.Base.TCEnv Agda.Termination.Monad.TerM instance Control.Monad.State.Class.MonadState Agda.TypeChecking.Monad.Base.TCState Agda.Termination.Monad.TerM instance Control.Monad.IO.Class.MonadIO Agda.Termination.Monad.TerM instance Agda.TypeChecking.Monad.Base.MonadTCM Agda.Termination.Monad.TerM instance Control.Monad.Error.Class.MonadError Agda.TypeChecking.Monad.Base.TCErr Agda.Termination.Monad.TerM instance Agda.Syntax.Abstract.IsProjP (Agda.Termination.Monad.DeBruijnPat' a) instance Agda.TypeChecking.Pretty.PrettyTCM Agda.Termination.Monad.DeBruijnPat instance Agda.Termination.Monad.UsableSizeVars Agda.Termination.Monad.DeBruijnPat instance Agda.Termination.Monad.UsableSizeVars Agda.Termination.Monad.DeBruijnPats instance Agda.Termination.Monad.UsableSizeVars (Agda.Termination.Monad.Masked Agda.Termination.Monad.DeBruijnPat) instance Agda.Termination.Monad.UsableSizeVars Agda.Termination.Monad.MaskedDeBruijnPats instance Agda.Utils.Functor.Decoration Agda.Termination.Monad.Masked instance Agda.TypeChecking.Pretty.PrettyTCM a => Agda.TypeChecking.Pretty.PrettyTCM (Agda.Termination.Monad.Masked a) instance Agda.Utils.Pretty.Pretty Agda.Termination.Monad.CallPath module Agda.TypeChecking.SizedTypes -- | Check whether a type is either not a SIZELT or a SIZELT that is -- non-empty. checkSizeLtSat :: Type -> TCM () -- | Precondition: Term is reduced and not blocked. Throws a -- patternViolation if undecided checkSizeNeverZero :: Term -> TCM Bool -- | Checks that a size variable is ensured to be > 0. E.g. -- variable i cannot be zero in context (i : Size) (j : -- Size< ↑ ↑ i) (k : Size< j) (k' : Size< k). Throws a -- patternViolation if undecided. checkSizeVarNeverZero :: Int -> TCM Bool -- | Check whether a variable in the context is bounded by a size -- expression. If x : Size< a, then a is returned. isBounded :: MonadTCM tcm => Nat -> tcm BoundedSize -- | Whenever we create a bounded size meta, add a constraint expressing -- the bound. In boundedSizeMetaHook v tel a, tel -- includes the current context. boundedSizeMetaHook :: Term -> Telescope -> Type -> TCM () -- | trySizeUniv cmp t m n x els1 y els2 is called as a last -- resort when conversion checking m cmp n : t failed -- for definitions m = x els1 and n = y els2, where the -- heads x and y are not equal. -- -- trySizeUniv accounts for subtyping between SIZELT and SIZE, -- like Size< i =< Size. -- -- If it does not succeed it reports failure of conversion check. trySizeUniv :: Comparison -> Type -> Term -> Term -> QName -> Elims -> QName -> Elims -> TCM () -- | Compute the deep size view of a term. Precondition: sized types are -- enabled. deepSizeView :: Term -> TCM DeepSizeView sizeMaxView :: Term -> TCM SizeMaxView -- | Compare two sizes. compareSizes :: Comparison -> Term -> Term -> TCM () -- | Compare two sizes in max view. compareMaxViews :: Comparison -> SizeMaxView -> SizeMaxView -> TCM () -- | compareBelowMax u vs checks u <= max vs. -- Precondition: size vs >= 2 compareBelowMax :: DeepSizeView -> SizeMaxView -> TCM () compareSizeViews :: Comparison -> DeepSizeView -> DeepSizeView -> TCM () -- | Checked whether a size constraint is trivial (like X <= -- X+1). trivial :: Term -> Term -> TCM Bool -- | Test whether a problem consists only of size constraints. isSizeProblem :: ProblemId -> TCM Bool -- | Test is a constraint speaks about sizes. isSizeConstraint :: Closure Constraint -> TCM Bool -- | Find the size constraints. getSizeConstraints :: TCM [Closure Constraint] -- | Return a list of size metas and their context. getSizeMetas :: Bool -> TCM [(MetaId, Type, Telescope)] -- | Atomic size expressions. data SizeExpr -- | A size meta applied to de Bruijn levels. SizeMeta :: MetaId -> [Int] -> SizeExpr -- | A de Bruijn level. Rigid :: Int -> SizeExpr -- | Size constraints we can solve. data SizeConstraint -- | Leq a +n b represents a =< b + n. Leq a -n -- b represents a + n =< b. Leq :: SizeExpr -> Int -> SizeExpr -> SizeConstraint -- | Compute a set of size constraints that all live in the same context -- from constraints over terms of type size that may live in different -- contexts. -- -- cf. simplifyLevelConstraint computeSizeConstraints :: [Closure Constraint] -> TCM [SizeConstraint] -- | Turn a constraint over de Bruijn levels into a size constraint. computeSizeConstraint :: Constraint -> TCM (Maybe SizeConstraint) -- | Turn a term with de Bruijn levels into a size expression with offset. -- -- Throws a patternViolation if the term isn't a proper size -- expression. sizeExpr :: Term -> TCM (SizeExpr, Int) -- | Compute list of size metavariables with their arguments appearing in a -- constraint. flexibleVariables :: SizeConstraint -> [(MetaId, [Int])] -- | Convert size constraint into form where each meta is applied to levels -- 0,1,..,n-1 where n is the arity of that meta. -- -- X[σ] <= t beomes X[id] <= t[σ^-1] -- -- X[σ] ≤ Y[τ] becomes X[id] ≤ Y[τ[σ^-1]] or -- X[σ[τ^1]] ≤ Y[id] whichever is defined. If none is defined, -- we give up. canonicalizeSizeConstraint :: SizeConstraint -> Maybe SizeConstraint -- | Main function. solveSizeConstraints :: TCM () -- | Old solver for size constraints using Agda.Utils.Warshall. oldSolver :: [(MetaId, Int)] -> [SizeConstraint] -> TCM Bool instance GHC.Classes.Eq Agda.TypeChecking.SizedTypes.SizeExpr instance GHC.Show.Show Agda.TypeChecking.SizedTypes.SizeExpr instance GHC.Show.Show Agda.TypeChecking.SizedTypes.SizeConstraint module Agda.TypeChecking.CompiledClause.Match matchCompiled :: CompiledClauses -> MaybeReducedArgs -> ReduceM (Reduced (Blocked Args) Term) -- | matchCompiledE c es takes a function given by case tree -- c and and a spine es and tries to apply the function -- to es. matchCompiledE :: CompiledClauses -> MaybeReducedElims -> ReduceM (Reduced (Blocked Elims) Term) -- | A stack entry is a triple consisting of 1. the part of the case tree -- to continue matching, 2. the current argument vector, and 3. a patch -- function taking the current argument vector back to the original -- argument vector. type Frame = (CompiledClauses, MaybeReducedElims, Elims -> Elims) type Stack = [Frame] -- | match' tries to solve the matching problems on the -- Stack. In each iteration, the top problem is removed and -- handled. -- -- If the top problem was a Done, we succeed. -- -- If the top problem was a Case n and the nth argument -- of the problem is not a constructor or literal, we are stuck, thus, -- fail. -- -- If we have a branch for the constructor/literal, we put it on the -- stack to continue. If we do not have a branch, we fall through to the -- next problem, which should be the corresponding catch-all branch. -- -- An empty stack is an exception that can come only from an incomplete -- function definition. match' :: Stack -> ReduceM (Reduced (Blocked Elims) Term) -- | Functions for inserting implicit arguments at the right places. module Agda.TypeChecking.Implicit -- | implicitArgs n expand t generates up to n implicit -- arguments metas (unbounded if n<0), as long as t -- is a function type and expand holds on the hiding info of its -- domain. implicitArgs :: Int -> (Hiding -> Bool) -> Type -> TCM (Args, Type) -- | implicitNamedArgs n expand t generates up to n named -- implicit arguments metas (unbounded if n<0), as long as -- t is a function type and expand holds on the hiding -- and name info of its domain. implicitNamedArgs :: Int -> (Hiding -> ArgName -> Bool) -> Type -> TCM (NamedArgs, Type) data ImplicitInsertion -- | this many implicits have to be inserted ImpInsert :: [Hiding] -> ImplicitInsertion -- | hidden argument where there should have been a non-hidden arg BadImplicits :: ImplicitInsertion -- | bad named argument NoSuchName :: ArgName -> ImplicitInsertion NoInsertNeeded :: ImplicitInsertion impInsert :: [Hiding] -> ImplicitInsertion -- | The list should be non-empty. insertImplicit :: NamedArg e -> [Arg ArgName] -> ImplicitInsertion instance GHC.Show.Show Agda.TypeChecking.Implicit.ImplicitInsertion -- | Pattern matcher used in the reducer for clauses that have not been -- compiled to case trees yet. module Agda.TypeChecking.Patterns.Match -- | If matching is inconclusive (DontKnow) we want to know -- whether it is due to a particular meta variable. data Match a Yes :: Simplification -> [a] -> Match a No :: Match a DontKnow :: (Blocked ()) -> Match a -- | Instead of zipWithM, we need to use this lazy version of -- combining pattern matching computations. foldMatch :: (p -> v -> ReduceM (Match Term, v)) -> [p] -> [v] -> ReduceM (Match Term, [v]) -- | matchCopatterns ps es matches spine es against -- copattern spine ps. -- -- Returns Yes and a substitution for the pattern variables (in -- form of [Term]) if matching was successful. -- -- Returns No if there was a constructor or projection mismatch. -- -- Returns DontKnow if an argument could not be evaluated to -- constructor form because of a blocking meta variable. -- -- In any case, also returns spine es in reduced form (with all -- the weak head reductions performed that were necessary to come to a -- decision). matchCopatterns :: [NamedArg Pattern] -> [Elim] -> ReduceM (Match Term, [Elim]) -- | Match a single copattern. matchCopattern :: Pattern -> Elim -> ReduceM (Match Term, Elim) matchPatterns :: [NamedArg Pattern] -> [Arg Term] -> ReduceM (Match Term, [Arg Term]) -- | Match a single pattern. matchPattern :: Pattern -> Arg Term -> ReduceM (Match Term, Arg Term) yesSimplification :: (Match a, b) -> (Match a, b) instance GHC.Base.Functor Agda.TypeChecking.Patterns.Match.Match instance Agda.Utils.Null.Null (Agda.TypeChecking.Patterns.Match.Match a) -- | Non-linear matching of the lhs of a rewrite rule against a neutral -- term. -- -- Given a lhs -- -- Δ ⊢ lhs : B -- -- and a candidate term -- -- Γ ⊢ t : A -- -- we seek a substitution Γ ⊢ σ : Δ such that -- -- Γ ⊢ B[σ] = A and Γ ⊢ lhs[σ] = t : A module Agda.TypeChecking.Rewriting.NonLinMatch -- | Turn a term into a non-linear pattern, treating the free variables as -- pattern variables. The first argument is the number of bound -- variables. class PatternFrom a b patternFrom :: PatternFrom a b => Int -> a -> TCM b -- | Monad for non-linear matching. type NLM = ExceptT Blocked_ (StateT NLMState ReduceM) type NLMState = (Sub, PostponedEquations) liftRed :: ReduceM a -> NLM a runNLM :: NLM () -> ReduceM (Either Blocked_ NLMState) traceSDocNLM :: VerboseKey -> Int -> TCM Doc -> NLM a -> NLM a matchingBlocked :: Blocked_ -> NLM () -- | Add substitution i |-> v to result of matching. tellSub :: Int -> Term -> NLM () tellEq :: Int -> Term -> Term -> NLM () type Sub = IntMap Term -- | Matching against a term produces a constraint which we have to verify -- after applying the substitution computed by matching. data PostponedEquation PostponedEquation :: Int -> Term -> Term -> PostponedEquation -- | Number of free variables in the equation [eqFreeVars] :: PostponedEquation -> Int -- | Term from pattern, living in pattern context. [eqLhs] :: PostponedEquation -> Term -- | Term from scrutinee, living in context where matching was invoked. [eqRhs] :: PostponedEquation -> Term type PostponedEquations = [PostponedEquation] -- | Match a non-linear pattern against a neutral term, returning a -- substitution. class Match a b match :: Match a b => Int -> a -> b -> NLM () makeSubstitution :: Sub -> Substitution checkPostponedEquations :: Substitution -> PostponedEquations -> ReduceM Bool nonLinMatch :: (Match a b) => a -> b -> ReduceM (Either Blocked_ Substitution) -- | Untyped βη-equality, does not handle things like empty record types. equal :: Term -> Term -> ReduceM Bool instance Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom a b => Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom [a] [b] instance Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom a b => Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom (Agda.Syntax.Internal.Arg a) (Agda.Syntax.Internal.Arg b) instance Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom a b => Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom (Agda.Syntax.Internal.Elim' a) (Agda.Syntax.Internal.Elim' b) instance Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom a b => Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom (Agda.Syntax.Internal.Dom a) (Agda.Syntax.Internal.Dom b) instance Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom a b => Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom (Agda.Syntax.Internal.Type' a) (Agda.Syntax.Internal.Type' b) instance Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom Agda.Syntax.Internal.Term Agda.TypeChecking.Monad.Base.NLPat instance Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom a b => Agda.TypeChecking.Rewriting.NonLinMatch.PatternFrom (Agda.Syntax.Internal.Abs a) (Agda.Syntax.Internal.Abs b) instance Agda.TypeChecking.Monad.Options.HasOptions Agda.TypeChecking.Rewriting.NonLinMatch.NLM instance Agda.TypeChecking.Rewriting.NonLinMatch.Match a b => Agda.TypeChecking.Rewriting.NonLinMatch.Match [a] [b] instance Agda.TypeChecking.Rewriting.NonLinMatch.Match a b => Agda.TypeChecking.Rewriting.NonLinMatch.Match (Agda.Syntax.Internal.Arg a) (Agda.Syntax.Internal.Arg b) instance Agda.TypeChecking.Rewriting.NonLinMatch.Match a b => Agda.TypeChecking.Rewriting.NonLinMatch.Match (Agda.Syntax.Internal.Elim' a) (Agda.Syntax.Internal.Elim' b) instance Agda.TypeChecking.Rewriting.NonLinMatch.Match a b => Agda.TypeChecking.Rewriting.NonLinMatch.Match (Agda.Syntax.Internal.Dom a) (Agda.Syntax.Internal.Dom b) instance Agda.TypeChecking.Rewriting.NonLinMatch.Match a b => Agda.TypeChecking.Rewriting.NonLinMatch.Match (Agda.Syntax.Internal.Type' a) (Agda.Syntax.Internal.Type' b) instance (Agda.TypeChecking.Rewriting.NonLinMatch.Match a b, Agda.TypeChecking.Substitute.Subst b, Agda.TypeChecking.Free.Free b, Agda.TypeChecking.Pretty.PrettyTCM a, Agda.TypeChecking.Pretty.PrettyTCM b) => Agda.TypeChecking.Rewriting.NonLinMatch.Match (Agda.Syntax.Internal.Abs a) (Agda.Syntax.Internal.Abs b) instance Agda.TypeChecking.Rewriting.NonLinMatch.Match Agda.TypeChecking.Monad.Base.NLPat Agda.Syntax.Internal.Term module Agda.TypeChecking.Errors prettyError :: MonadTCM tcm => TCErr -> tcm String tcErrString :: TCErr -> String -- | Warnings. -- -- Invariant: The fields are never empty at the same time. data Warnings Warnings :: [Range] -> Constraints -> Warnings -- | Meta-variable problems are reported as type errors unless -- optAllowUnsolved is True. [unsolvedMetaVariables] :: Warnings -> [Range] -- | Same as unsolvedMetaVariables. [unsolvedConstraints] :: Warnings -> Constraints -- | Turns warnings into an error. Even if several errors are possible only -- one is raised. warningsToError :: Warnings -> TCM a instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.TCErr instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.CallInfo instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.TypeError instance Agda.TypeChecking.Errors.PrettyUnequal Agda.Syntax.Internal.Term instance Agda.TypeChecking.Errors.PrettyUnequal Agda.Syntax.Internal.Type instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.SplitError instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Monad.Base.Call instance Agda.TypeChecking.Errors.Verbalize Agda.Syntax.Common.Hiding instance Agda.TypeChecking.Errors.Verbalize Agda.Syntax.Common.Relevance instance Agda.TypeChecking.Errors.Verbalize a => Agda.TypeChecking.Errors.Verbalize (Agda.TypeChecking.Errors.Indefinite a) -- | Code which replaces pattern matching on record constructors with uses -- of projection functions. module Agda.TypeChecking.RecordPatterns -- | Replaces pattern matching on record constructors with uses of -- projection functions. Does not remove record constructor patterns -- which have sub-patterns containing non-record constructor or literal -- patterns. translateRecordPatterns :: Clause -> TCM Clause translateCompiledClauses :: CompiledClauses -> TCM CompiledClauses -- | Bottom-up procedure to record-pattern-translate split tree. translateSplitTree :: SplitTree -> TCM SplitTree -- | Take a record pattern p and yield a list of projections -- corresponding to the pattern variables, from left to right. -- -- E.g. for (x , (y , z)) we return [ fst, fst . snd, snd . -- snd ]. -- -- If it is not a record pattern, error ShouldBeRecordPattern is -- raised. recordPatternToProjections :: Pattern -> TCM [Term -> Term] instance GHC.Classes.Eq Agda.TypeChecking.RecordPatterns.Kind instance Control.Monad.State.Class.MonadState Agda.TypeChecking.Monad.Base.TCState Agda.TypeChecking.RecordPatterns.RecPatM instance Control.Monad.Reader.Class.MonadReader Agda.TypeChecking.Monad.Base.TCEnv Agda.TypeChecking.RecordPatterns.RecPatM instance Agda.TypeChecking.Monad.Base.MonadTCM Agda.TypeChecking.RecordPatterns.RecPatM instance Control.Monad.IO.Class.MonadIO Agda.TypeChecking.RecordPatterns.RecPatM instance GHC.Base.Monad Agda.TypeChecking.RecordPatterns.RecPatM instance GHC.Base.Applicative Agda.TypeChecking.RecordPatterns.RecPatM instance GHC.Base.Functor Agda.TypeChecking.RecordPatterns.RecPatM instance Agda.TypeChecking.RecordPatterns.DropFrom (Agda.TypeChecking.Coverage.SplitTree.SplitTree' c) instance Agda.TypeChecking.RecordPatterns.DropFrom (c, Agda.TypeChecking.Coverage.SplitTree.SplitTree' c) instance Agda.TypeChecking.RecordPatterns.DropFrom a => Agda.TypeChecking.RecordPatterns.DropFrom [a] instance Agda.Utils.Pretty.Pretty (Agda.TypeChecking.RecordPatterns.Kind -> Agda.Syntax.Common.Nat) instance Agda.TypeChecking.Pretty.PrettyTCM (Agda.TypeChecking.RecordPatterns.Kind -> Agda.Syntax.Common.Nat) instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.RecordPatterns.Change module Agda.TypeChecking.InstanceArguments -- | A candidate solution for an instance meta is a term with its type. type Candidate = (Term, Type) type Candidates = [Candidate] -- | Compute a list of instance candidates. Nothing if type is a -- meta, error if type is not eligible for instance search. initialIFSCandidates :: Type -> TCM (Maybe Candidates) -- | initializeIFSMeta s t generates an instance meta of type -- t with suggested name s. initializeIFSMeta :: String -> Type -> TCM Term -- | findInScope m (v,a)s tries to instantiate on of the types -- as of the candidate terms vs to the type t -- of the metavariable m. If successful, meta m is -- solved with the instantiation of v. If unsuccessful, the -- constraint is regenerated, with possibly reduced candidate set. The -- list of candidates is equal to Nothing when the type of the -- meta wasn't known when the constraint was generated. In that case, try -- to find its type again. findInScope :: MetaId -> Maybe Candidates -> TCM () -- | Result says whether we need to add constraint, and if so, the set of -- remaining candidates. findInScope' :: MetaId -> Candidates -> TCM (Maybe Candidates) -- | A meta _M is rigidly constrained if there is a constraint _M us == D -- vs, for inert D. Such metas can safely be instantiated by recursive -- instance search, since the constraint limits the solution space. rigidlyConstrainedMetas :: TCM [MetaId] -- | Given a meta m of type t and a list of candidates -- cands, checkCandidates m t cands returns a refined -- list of valid candidates. checkCandidates :: MetaId -> Type -> Candidates -> TCM Candidates -- | To preserve the invariant that a constructor is not applied to its -- parameter arguments, we explicitly check whether function term we are -- applying to arguments is a unapplied constructor. In this case we drop -- the first conPars arguments. See Issue670a. Andreas, 2013-11-07 -- Also do this for projections, see Issue670b. applyDroppingParameters :: Term -> Args -> TCM Term module Agda.TypeChecking.Constraints -- | Catches pattern violation errors and adds a constraint. catchConstraint :: Constraint -> TCM () -> TCM () addConstraint :: Constraint -> TCM () -- | Don't allow the argument to produce any constraints. noConstraints :: TCM a -> TCM a -- | Create a fresh problem for the given action. newProblem :: TCM a -> TCM (ProblemId, a) newProblem_ :: TCM () -> TCM ProblemId ifNoConstraints :: TCM a -> (a -> TCM b) -> (ProblemId -> a -> TCM b) -> TCM b ifNoConstraints_ :: TCM () -> TCM a -> (ProblemId -> TCM a) -> TCM a -- | guardConstraint c blocker tries to solve blocker -- first. If successful without constraints, it moves on to solve -- c, otherwise it adds a Guarded c cs constraint to -- the blocker-generated constraints cs. guardConstraint :: Constraint -> TCM () -> TCM () whenConstraints :: TCM () -> TCM () -> TCM () -- | Wake up the constraints depending on the given meta. wakeupConstraints :: MetaId -> TCM () -- | Wake up all constraints. wakeupConstraints_ :: TCM () solveAwakeConstraints :: TCM () solveAwakeConstraints' :: Bool -> TCM () solveConstraint :: Constraint -> TCM () solveConstraint_ :: Constraint -> TCM () checkTypeCheckingProblem :: TypeCheckingProblem -> TCM Term module Agda.TypeChecking.Rules.LHS.Implicit -- | Insert implicit patterns in a problem. insertImplicitProblem :: Problem -> TCM Problem -- | Eta-expand implicit pattern if of record type. expandImplicitPattern :: Type -> NamedArg Pattern -> TCM (NamedArg Pattern) -- | Try to eta-expand implicit pattern. Returns Nothing unless -- dealing with a record type that has eta-expansion and a constructor -- c. In this case, it returns Just c _ _ ... _ -- (record constructor applied to as many implicit patterns as there are -- fields). expandImplicitPattern' :: Type -> NamedArg Pattern -> TCM (Maybe (NamedArg Pattern)) implicitP :: Named_ Pattern -- | Insert implicit patterns in a list of patterns. Even if -- DontExpandLast, trailing SIZELT patterns are inserted. insertImplicitPatterns :: ExpandHidden -> [NamedArg Pattern] -> Telescope -> TCM [NamedArg Pattern] -- | Insert trailing SizeLt patterns, if any. insertImplicitSizeLtPatterns :: Type -> TCM [NamedArg Pattern] -- | Insert implicit patterns in a list of patterns. Even if -- DontExpandLast, trailing SIZELT patterns are inserted. insertImplicitPatternsT :: ExpandHidden -> [NamedArg Pattern] -> Type -> TCM [NamedArg Pattern] -- | This module defines an inlining transformation on clauses that's run -- before termination checking. The purpose is to improve termination -- checking of with clauses (issue 59). The transformation inlines -- generated with-functions expanding the clauses of the parent function -- in such a way that termination checking the expanded clauses -- guarantees termination of the original function, while allowing more -- terminating functions to be accepted. It does in no way pretend to -- preserve the semantics of the original function. -- -- Roughly, the source program -- --
--   f ps with as
--   {f ps₁i qsi = bi}
--   
-- -- is represented internally as -- --
--   f ps = f-aux xs as      where xs   = vars(ps)
--   {f-aux ps₂i qsi = bi}   where ps₁i = ps[ps₂i/xs]
--   
-- -- The inlining transformation turns this into -- --
--   {f ps = aj} for aj ∈ as
--   {f ps₁i qsi = bi}
--   
-- -- The first set of clauses, called withExprClauses, ensure that -- we don't forget any recursive calls in as. The second set of -- clauses, henceforth called inlinedClauses, are the -- surface-level clauses the user sees (and probably reasons about). -- -- The reason this works is that there is a single call site for each -- with-function. -- -- Note that the lhss of the inlined clauses are not type-correct, -- neither with the type of f (since there are additional -- patterns qsi) nor with the type of f-aux (since -- there are the surface-level patterns ps₁i instead of the -- actual patterns ps₂i). module Agda.Termination.Inlining inlineWithClauses :: QName -> Clause -> TCM [Clause] isWithFunction :: MonadTCM tcm => QName -> tcm (Maybe QName) expandWithFunctionCall :: QName -> Elims -> TCM Term module Agda.Termination.TermCheck -- | Entry point: Termination check a single declaration. termDecl :: Declaration -> TCM Result -- | The result of termination checking a module. Must be a Monoid -- and have Singleton. type Result = [TerminationError] -- | Patterns with variables as de Bruijn indices. type DeBruijnPat = DeBruijnPat' Int instance Agda.Termination.TermCheck.ExtractCalls Agda.Syntax.Internal.Level instance Agda.Termination.TermCheck.ExtractCalls a => Agda.Termination.TermCheck.ExtractCalls (Agda.Syntax.Internal.Abs a) instance Agda.Termination.TermCheck.ExtractCalls a => Agda.Termination.TermCheck.ExtractCalls (Agda.Syntax.Internal.Arg a) instance Agda.Termination.TermCheck.ExtractCalls a => Agda.Termination.TermCheck.ExtractCalls (Agda.Syntax.Internal.Dom a) instance Agda.Termination.TermCheck.ExtractCalls a => Agda.Termination.TermCheck.ExtractCalls (Agda.Syntax.Internal.Elim' a) instance Agda.Termination.TermCheck.ExtractCalls a => Agda.Termination.TermCheck.ExtractCalls [a] instance (Agda.Termination.TermCheck.ExtractCalls a, Agda.Termination.TermCheck.ExtractCalls b) => Agda.Termination.TermCheck.ExtractCalls (a, b) instance Agda.Termination.TermCheck.ExtractCalls Agda.Syntax.Internal.Sort instance Agda.Termination.TermCheck.ExtractCalls Agda.Syntax.Internal.Type instance Agda.Termination.TermCheck.ExtractCalls Agda.Syntax.Internal.Term instance Agda.Termination.TermCheck.ExtractCalls Agda.Syntax.Internal.PlusLevel instance Agda.Termination.TermCheck.ExtractCalls Agda.Syntax.Internal.LevelAtom instance Agda.Termination.TermCheck.StripAllProjections a => Agda.Termination.TermCheck.StripAllProjections (Agda.Syntax.Internal.Arg a) instance Agda.Termination.TermCheck.StripAllProjections Agda.Syntax.Internal.Elims instance Agda.Termination.TermCheck.StripAllProjections Agda.Syntax.Internal.Args instance Agda.Termination.TermCheck.StripAllProjections Agda.Syntax.Internal.Term -- | Check that a datatype is strictly positive. module Agda.TypeChecking.Positivity type Graph n e = Graph n n e -- | Check that the datatypes in the mutual block containing the given -- declarations are strictly positive. -- -- Also add information about positivity and recursivity of records to -- the signature. checkStrictlyPositive :: Set QName -> TCM () getDefArity :: Definition -> TCM Int -- | Description of an occurrence. data OccursWhere LeftOfArrow :: OccursWhere -> OccursWhere -- | in the nth argument of a define constant DefArg :: QName -> Nat -> OccursWhere -> OccursWhere -- | in the principal argument of built-in ∞ UnderInf :: OccursWhere -> OccursWhere -- | as an argument to a bound variable VarArg :: OccursWhere -> OccursWhere -- | as an argument of a metavariable MetaArg :: OccursWhere -> OccursWhere -- | in the type of a constructor ConArgType :: QName -> OccursWhere -> OccursWhere -- | in a datatype index of a constructor IndArgType :: QName -> OccursWhere -> OccursWhere -- | in the nth clause of a defined function InClause :: Nat -> OccursWhere -> OccursWhere -- | matched against in a clause of a defined function Matched :: OccursWhere -> OccursWhere -- | in the definition of a constant InDefOf :: QName -> OccursWhere -> OccursWhere Here :: OccursWhere -- | an unknown position (treated as negative) Unknown :: OccursWhere (>*<) :: OccursWhere -> OccursWhere -> OccursWhere data Item AnArg :: Nat -> Item ADef :: QName -> Item type Occurrences = Map Item [OccursWhere] (>+<) :: Occurrences -> Occurrences -> Occurrences concatOccurs :: [Occurrences] -> Occurrences occursAs :: (OccursWhere -> OccursWhere) -> Occurrences -> Occurrences here :: Item -> Occurrences -- | onlyVarsUpTo n occs discards occurrences of de Bruijn index -- >= n. onlyVarsUpTo :: Nat -> Occurrences -> Occurrences -- | Context for computing occurrences. data OccEnv OccEnv :: [Maybe Item] -> Maybe QName -> OccEnv -- | Items corresponding to the free variables. [vars] :: OccEnv -> [Maybe Item] -- | Name for ∞ builtin. [inf] :: OccEnv -> Maybe QName -- | Monad for computing occurrences. type OccM = Reader OccEnv withExtendedOccEnv :: Maybe Item -> OccM a -> OccM a -- | Running the monad getOccurrences :: (Show a, PrettyTCM a, ComputeOccurrences a) => [Maybe Item] -> a -> TCM Occurrences class ComputeOccurrences a occurrences :: ComputeOccurrences a => a -> OccM Occurrences -- | Compute the occurrences in a given definition. computeOccurrences :: QName -> TCM Occurrences -- | Eta expand a clause to have the given number of variables. Warning: -- doesn't put correct types in telescope! This is used instead of -- special treatment of lambdas (which was unsound: issue 121) etaExpandClause :: Nat -> Clause -> Clause data Node DefNode :: QName -> Node ArgNode :: QName -> Nat -> Node -- | Edge labels for the positivity graph. data Edge Edge :: Occurrence -> OccursWhere -> Edge -- | These operations form a semiring if we quotient by the relation "the -- Occurrence components are equal". -- | As OccursWhere does not have an oplus we cannot do -- something meaningful for the OccursWhere here. -- -- E.g. ostar (Edge JustNeg w) = Edge Mixed (w oplus (w -- >*< w)) would probably more sense, if we could do it. buildOccurrenceGraph :: Set QName -> TCM (Graph Node Edge) -- | Given an OccursWhere computes the target node and an -- Edge. The first argument is the set of names in the current -- mutual block. computeEdge :: Set QName -> OccursWhere -> TCM (Node, Edge) instance GHC.Show.Show Agda.TypeChecking.Positivity.Edge instance GHC.Classes.Ord Agda.TypeChecking.Positivity.Edge instance GHC.Classes.Eq Agda.TypeChecking.Positivity.Edge instance GHC.Classes.Ord Agda.TypeChecking.Positivity.Node instance GHC.Classes.Eq Agda.TypeChecking.Positivity.Node instance GHC.Show.Show Agda.TypeChecking.Positivity.Item instance GHC.Classes.Ord Agda.TypeChecking.Positivity.Item instance GHC.Classes.Eq Agda.TypeChecking.Positivity.Item instance GHC.Classes.Ord Agda.TypeChecking.Positivity.OccursWhere instance GHC.Classes.Eq Agda.TypeChecking.Positivity.OccursWhere instance GHC.Show.Show Agda.TypeChecking.Positivity.OccursWhere instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Positivity.OccursWhere instance Agda.TypeChecking.Positivity.ComputeOccurrences Agda.Syntax.Internal.Clause instance Agda.TypeChecking.Positivity.ComputeOccurrences Agda.Syntax.Internal.Term instance Agda.TypeChecking.Positivity.ComputeOccurrences Agda.Syntax.Internal.Level instance Agda.TypeChecking.Positivity.ComputeOccurrences Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Positivity.ComputeOccurrences Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.Positivity.ComputeOccurrences Agda.Syntax.Internal.Type instance Agda.TypeChecking.Positivity.ComputeOccurrences a => Agda.TypeChecking.Positivity.ComputeOccurrences (Agda.Syntax.Internal.Tele a) instance Agda.TypeChecking.Positivity.ComputeOccurrences a => Agda.TypeChecking.Positivity.ComputeOccurrences (Agda.Syntax.Internal.Abs a) instance Agda.TypeChecking.Positivity.ComputeOccurrences a => Agda.TypeChecking.Positivity.ComputeOccurrences (Agda.Syntax.Internal.Elim' a) instance Agda.TypeChecking.Positivity.ComputeOccurrences a => Agda.TypeChecking.Positivity.ComputeOccurrences (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.Positivity.ComputeOccurrences a => Agda.TypeChecking.Positivity.ComputeOccurrences (Agda.Syntax.Internal.Dom a) instance Agda.TypeChecking.Positivity.ComputeOccurrences a => Agda.TypeChecking.Positivity.ComputeOccurrences [a] instance (Agda.TypeChecking.Positivity.ComputeOccurrences a, Agda.TypeChecking.Positivity.ComputeOccurrences b) => Agda.TypeChecking.Positivity.ComputeOccurrences (a, b) instance GHC.Show.Show Agda.TypeChecking.Positivity.Node instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Positivity.Node instance Agda.TypeChecking.Pretty.PrettyTCM n => Agda.TypeChecking.Pretty.PrettyTCM (Agda.TypeChecking.Pretty.WithNode n Agda.TypeChecking.Positivity.Edge) instance Agda.Utils.Null.Null Agda.TypeChecking.Positivity.Edge instance Agda.Utils.SemiRing.SemiRing Agda.TypeChecking.Positivity.Edge instance Agda.Utils.SemiRing.StarSemiRing Agda.TypeChecking.Positivity.Edge instance Test.QuickCheck.Arbitrary.Arbitrary Agda.TypeChecking.Positivity.OccursWhere instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.TypeChecking.Positivity.OccursWhere instance Test.QuickCheck.Arbitrary.Arbitrary Agda.TypeChecking.Positivity.Edge instance Test.QuickCheck.Arbitrary.CoArbitrary Agda.TypeChecking.Positivity.Edge module Agda.TypeChecking.Positivity.Tests -- | The oplus method for Occurrence matches that for -- Edge. prop_oplus_Occurrence_Edge :: Edge -> Edge -> Bool -- | Tests. tests :: IO Bool module Agda.TypeChecking.Tests -- |
--   telFromList . telToList == id
--   
prop_telToListInv :: TermConfiguration -> Property -- | All elements of flattenTel are well-scoped under the original -- telescope. prop_flattenTelScope :: TermConfiguration -> Property -- |
--   unflattenTel . flattenTel == id
--   
prop_flattenTelInv :: TermConfiguration -> Property -- | reorderTel is stable. prop_reorderTelStable :: TermConfiguration -> Property -- | The result of splitting a telescope is well-scoped. prop_splitTelescopeScope :: TermConfiguration -> Property -- | The permutation generated when splitting a telescope preserves -- scoping. prop_splitTelescopePermScope :: TermConfiguration -> Property tests :: IO Bool module Agda.Utils.Permutation.Tests -- | All tests as collected by quickCheckAll. tests :: IO Bool instance GHC.Show.Show Agda.Utils.Permutation.Tests.ComposablePermutations instance GHC.Classes.Eq Agda.Utils.Permutation.Tests.ComposablePermutations instance Test.QuickCheck.Arbitrary.Arbitrary Agda.Utils.Permutation.Tests.ComposablePermutations module Agda.TypeChecking.ProjectionLike -- | View for a Def f (Apply a : es) where isProjection -- f. Used for projection-like fs. data ProjectionView -- | A projection or projection-like function, applied to its principal -- argument ProjectionView :: QName -> Arg Term -> Elims -> ProjectionView [projViewProj] :: ProjectionView -> QName [projViewSelf] :: ProjectionView -> Arg Term [projViewSpine] :: ProjectionView -> Elims -- | Just a lone projection-like function, missing its principal argument -- (from which we could infer the parameters). LoneProjectionLike :: QName -> ArgInfo -> ProjectionView -- | Not a projection or projection-like thing. NoProjection :: Term -> ProjectionView -- | Semantics of ProjectionView. unProjView :: ProjectionView -> Term -- | Top-level ProjectionView (no reduction). projView :: HasConstInfo m => Term -> m ProjectionView -- | Reduce away top-level projection like functions. (Also reduces -- projections, but they should not be there, since Internal is in -- lambda- and projection-beta-normal form.) reduceProjectionLike :: Term -> TCM Term -- | Turn prefix projection-like function application into postfix ones. -- This does just one layer, such that the top spine contains the -- projection-like functions as projections. Used in -- compareElims in TypeChecking.Conversion and in -- Agda.TypeChecking.CheckInternal. -- -- If the Bool is True, a lone projection like function -- will be turned into a lambda-abstraction, expecting the principal -- argument. If the Bool is False, it will be returned -- unaltered. -- -- No precondition. Preserves constructorForm, since it really does only -- something on (applications of) projection-like functions. elimView :: Bool -> Term -> TCM Term -- | Which Deftypes are eligible for the principle argument of a -- projection-like function? eligibleForProjectionLike :: QName -> TCM Bool -- | Turn a definition into a projection if it looks like a projection. makeProjection :: QName -> TCM () -- | The occurs check for unification. Does pruning on the fly. -- -- When hitting a meta variable: -- -- module Agda.TypeChecking.MetaVars.Occurs modifyOccursCheckDefs :: (Set QName -> Set QName) -> TCM () -- | Set the names of definitions to be looked at to the defs in the -- current mutual block. initOccursCheck :: MetaVariable -> TCM () -- | Is a def in the list of stuff to be checked? defNeedsChecking :: QName -> TCM Bool -- | Remove a def from the list of defs to be looked at. tallyDef :: QName -> TCM () data OccursCtx -- | we are in arguments of a meta Flex :: OccursCtx -- | we are not in arguments of a meta but a bound var Rigid :: OccursCtx -- | we are at the start or in the arguments of a constructor StronglyRigid :: OccursCtx -- | we are at the term root (this turns into StronglyRigid) Top :: OccursCtx -- | we are in an irrelevant argument Irrel :: OccursCtx data UnfoldStrategy YesUnfold :: UnfoldStrategy NoUnfold :: UnfoldStrategy defArgs :: UnfoldStrategy -> OccursCtx -> OccursCtx unfold :: UnfoldStrategy -> Term -> TCM (Blocked Term) -- | Leave the top position. leaveTop :: OccursCtx -> OccursCtx -- | Leave the strongly rigid position. weakly :: OccursCtx -> OccursCtx strongly :: OccursCtx -> OccursCtx patternViolation' :: Int -> String -> TCM a abort :: OccursCtx -> TypeError -> TCM a -- | Distinguish relevant and irrelevant variables in occurs check. type Vars = ([Nat], [Nat]) goIrrelevant :: Vars -> Vars allowedVar :: Nat -> Vars -> Bool takeRelevant :: Vars -> [Nat] liftUnderAbs :: Vars -> Vars -- | Extended occurs check. class Occurs t occurs :: Occurs t => UnfoldStrategy -> OccursCtx -> MetaId -> Vars -> t -> TCM t metaOccurs :: Occurs t => MetaId -> t -> TCM () -- | When assigning m xs := v, check that m does not -- occur in v and that the free variables of v are -- contained in xs. occursCheck :: (Occurs a, InstantiateFull a, PrettyTCM a) => MetaId -> Vars -> a -> TCM a -- | prune m' vs xs attempts to remove all arguments from -- vs whose free variables are not contained in xs. If -- successful, m' is solved by the new, pruned meta variable and -- we return True else False. -- -- Issue 1147: If any of the meta args vs is matchable, e.g., is -- a constructor term, we cannot prune, because the offending variables -- could be removed by reduction for a suitable instantiation of the meta -- variable. prune :: MetaId -> Args -> [Nat] -> TCM PruneResult -- | hasBadRigid xs v = Just True iff one of the rigid variables -- in v is not in xs. Actually we can only prune if a -- bad variable is in the head. See issue 458. Or in a non-eliminateable -- position (see succeed/PruningNonMillerPattern). -- -- hasBadRigid xs v = Nothing means that we cannot prune at all -- as one of the meta args is matchable. (See issue 1147.) hasBadRigid :: [Nat] -> Term -> ExceptT () TCM Bool -- | Check whether a term Def f es is finally stuck. Currently, we -- give only a crude approximation. isNeutral :: MonadTCM tcm => Blocked t -> QName -> Elims -> tcm Bool -- | Check whether any of the variables (given as de Bruijn indices) occurs -- *definitely* in the term in a rigid position. Reduces the term -- successively to remove variables in dead subterms. This fixes issue -- 1386. rigidVarsNotContainedIn :: (MonadTCM tcm, FoldRigid a) => a -> [Nat] -> tcm Bool -- | Collect the *definitely* rigid variables in a monoid. We need to -- successively reduce the expression to do this. class FoldRigid a foldRigid :: (FoldRigid a, Monoid (TCM m)) => (TCM m -> TCM m) -> (Nat -> TCM m) -> a -> TCM m data PruneResult -- | the kill list is empty or only Falses NothingToPrune :: PruneResult -- | there is no possible kill (because of type dep.) PrunedNothing :: PruneResult -- | managed to kill some args in the list PrunedSomething :: PruneResult -- | all prescribed kills where performed PrunedEverything :: PruneResult -- | killArgs [k1,...,kn] X prunes argument i from -- metavar X if ki==True. Pruning is carried out -- whenever > 0 arguments can be pruned. True is only -- returned if all arguments could be pruned. killArgs :: [Bool] -> MetaId -> TCM PruneResult -- | killedType [((x1,a1),k1)..((xn,an),kn)] b = ([k'1..k'n],t') -- (ignoring Dom). Let t' = (xs:as) -> b. Invariant: -- k'i == True iff ki == True and pruning the -- ith argument from type b is possible without -- creating unbound variables. t' is type t after -- pruning all k'i==True. killedType :: [(Dom (ArgName, Type), Bool)] -> Type -> ([Arg Bool], Type) performKill :: [Arg Bool] -> MetaId -> Type -> TCM () instance GHC.Show.Show Agda.TypeChecking.MetaVars.Occurs.PruneResult instance GHC.Classes.Eq Agda.TypeChecking.MetaVars.Occurs.PruneResult instance GHC.Show.Show Agda.TypeChecking.MetaVars.Occurs.UnfoldStrategy instance GHC.Classes.Eq Agda.TypeChecking.MetaVars.Occurs.UnfoldStrategy instance GHC.Show.Show Agda.TypeChecking.MetaVars.Occurs.OccursCtx instance GHC.Classes.Eq Agda.TypeChecking.MetaVars.Occurs.OccursCtx instance Agda.TypeChecking.MetaVars.Occurs.Occurs Agda.Syntax.Internal.Term instance Agda.TypeChecking.MetaVars.Occurs.Occurs Agda.Syntax.Abstract.Name.QName instance Agda.TypeChecking.MetaVars.Occurs.Occurs Agda.TypeChecking.Monad.Base.Defn instance Agda.TypeChecking.MetaVars.Occurs.Occurs Agda.Syntax.Internal.Clause instance Agda.TypeChecking.MetaVars.Occurs.Occurs Agda.Syntax.Internal.Level instance Agda.TypeChecking.MetaVars.Occurs.Occurs Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.MetaVars.Occurs.Occurs Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.MetaVars.Occurs.Occurs Agda.Syntax.Internal.Type instance Agda.TypeChecking.MetaVars.Occurs.Occurs Agda.Syntax.Internal.Sort instance Agda.TypeChecking.MetaVars.Occurs.Occurs a => Agda.TypeChecking.MetaVars.Occurs.Occurs (Agda.Syntax.Internal.Elim' a) instance (Agda.TypeChecking.MetaVars.Occurs.Occurs a, Agda.TypeChecking.Substitute.Subst a) => Agda.TypeChecking.MetaVars.Occurs.Occurs (Agda.Syntax.Internal.Abs a) instance Agda.TypeChecking.MetaVars.Occurs.Occurs a => Agda.TypeChecking.MetaVars.Occurs.Occurs (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.MetaVars.Occurs.Occurs a => Agda.TypeChecking.MetaVars.Occurs.Occurs (Agda.Syntax.Internal.Dom a) instance (Agda.TypeChecking.MetaVars.Occurs.Occurs a, Agda.TypeChecking.MetaVars.Occurs.Occurs b) => Agda.TypeChecking.MetaVars.Occurs.Occurs (a, b) instance Agda.TypeChecking.MetaVars.Occurs.Occurs a => Agda.TypeChecking.MetaVars.Occurs.Occurs [a] instance Agda.TypeChecking.MetaVars.Occurs.FoldRigid Agda.Syntax.Internal.Term instance Agda.TypeChecking.MetaVars.Occurs.FoldRigid Agda.Syntax.Internal.Type instance Agda.TypeChecking.MetaVars.Occurs.FoldRigid Agda.Syntax.Internal.Sort instance Agda.TypeChecking.MetaVars.Occurs.FoldRigid Agda.Syntax.Internal.Level instance Agda.TypeChecking.MetaVars.Occurs.FoldRigid Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.MetaVars.Occurs.FoldRigid Agda.Syntax.Internal.LevelAtom instance (Agda.TypeChecking.Substitute.Subst a, Agda.TypeChecking.MetaVars.Occurs.FoldRigid a) => Agda.TypeChecking.MetaVars.Occurs.FoldRigid (Agda.Syntax.Internal.Abs a) instance Agda.TypeChecking.MetaVars.Occurs.FoldRigid a => Agda.TypeChecking.MetaVars.Occurs.FoldRigid (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.MetaVars.Occurs.FoldRigid a => Agda.TypeChecking.MetaVars.Occurs.FoldRigid (Agda.Syntax.Internal.Dom a) instance Agda.TypeChecking.MetaVars.Occurs.FoldRigid a => Agda.TypeChecking.MetaVars.Occurs.FoldRigid (Agda.Syntax.Internal.Elim' a) instance Agda.TypeChecking.MetaVars.Occurs.FoldRigid a => Agda.TypeChecking.MetaVars.Occurs.FoldRigid [a] instance (Agda.TypeChecking.MetaVars.Occurs.FoldRigid a, Agda.TypeChecking.MetaVars.Occurs.FoldRigid b) => Agda.TypeChecking.MetaVars.Occurs.FoldRigid (a, b) module Agda.TypeChecking.MetaVars -- | Find position of a value in a list. Used to change metavar argument -- indices during assignment. -- -- reverse is necessary because we are directly abstracting over -- the list. findIdx :: Eq a => [a] -> a -> Maybe Int -- | Check whether a meta variable is a place holder for a blocked term. isBlockedTerm :: MetaId -> TCM Bool isEtaExpandable :: MetaId -> TCM Bool -- | Performing the meta variable assignment. -- -- The instantiation should not be an InstV or InstS and -- the MetaId should point to something Open or a -- BlockedConst. Further, the meta variable may not be -- Frozen. assignTerm :: MetaId -> [Arg ArgName] -> Term -> TCM () -- | Skip frozen check. Used for eta expanding frozen metas. assignTerm' :: MetaId -> [Arg ArgName] -> Term -> TCM () newSortMeta :: TCM Sort newSortMetaCtx :: Args -> TCM Sort newTypeMeta :: Sort -> TCM Type newTypeMeta_ :: TCM Type -- | newIFSMeta s t cands creates a new "implicit from scope" -- metavariable of type the output type of t with name -- suggestion s and initial solution candidates cands. -- If t is a function type, then insert enough lambdas in front -- of it. newIFSMeta :: MetaNameSuggestion -> Type -> Maybe [(Term, Type)] -> TCM Term -- | Create a new value meta with specific dependencies. newIFSMetaCtx :: MetaNameSuggestion -> Type -> Args -> Maybe [(Term, Type)] -> TCM Term newNamedValueMeta :: RunMetaOccursCheck -> MetaNameSuggestion -> Type -> TCM Term -- | Create a new metavariable, possibly η-expanding in the process. newValueMeta :: RunMetaOccursCheck -> Type -> TCM Term newValueMetaCtx :: RunMetaOccursCheck -> Type -> Args -> TCM Term -- | Create a new value meta without η-expanding. newValueMeta' :: RunMetaOccursCheck -> Type -> TCM Term -- | Create a new value meta with specific dependencies. newValueMetaCtx' :: RunMetaOccursCheck -> Type -> Args -> TCM Term newTelMeta :: Telescope -> TCM Args type Condition = Dom Type -> Abs Type -> Bool trueCondition :: Condition newArgsMeta :: Type -> TCM Args newArgsMeta' :: Condition -> Type -> TCM Args newArgsMetaCtx :: Type -> Telescope -> Args -> TCM Args newArgsMetaCtx' :: Condition -> Type -> Telescope -> Args -> TCM Args -- | Create a metavariable of record type. This is actually one -- metavariable for each field. newRecordMeta :: QName -> Args -> TCM Term newRecordMetaCtx :: QName -> Args -> Telescope -> Args -> TCM Term newQuestionMark :: InteractionId -> Type -> TCM Term -- | Construct a blocked constant if there are constraints. blockTerm :: Type -> TCM Term -> TCM Term blockTermOnProblem :: Type -> Term -> ProblemId -> TCM Term blockTypeOnProblem :: Type -> ProblemId -> TCM Type -- | unblockedTester t returns False if t is a -- meta or a blocked term. -- -- Auxiliary function to create a postponed type checking problem. unblockedTester :: Type -> TCM Bool -- | Create a postponed type checking problem e : t that waits for -- type t to unblock (become instantiated or its constraints -- resolved). postponeTypeCheckingProblem_ :: TypeCheckingProblem -> TCM Term -- | Create a postponed type checking problem e : t that waits for -- conditon unblock. A new meta is created in the current -- context that has as instantiation the postponed type checking problem. -- An UnBlock constraint is added for this meta, which links to -- this meta. postponeTypeCheckingProblem :: TypeCheckingProblem -> TCM Bool -> TCM Term -- | Type of the term that is produced by solving the -- TypeCheckingProblem. problemType :: TypeCheckingProblem -> Type -- | Eta expand metavariables listening on the current meta. etaExpandListeners :: MetaId -> TCM () -- | Wake up a meta listener and let it do its thing wakeupListener :: Listener -> TCM () -- | Do safe eta-expansions for meta (SingletonRecords,Levels). etaExpandMetaSafe :: MetaId -> TCM () -- | Various kinds of metavariables. data MetaKind -- | Meta variables of record type. Records :: MetaKind -- | Meta variables of "hereditarily singleton" record type. SingletonRecords :: MetaKind -- | Meta variables of level type, if type-in-type is activated. Levels :: MetaKind -- | All possible metavariable kinds. allMetaKinds :: [MetaKind] -- | Eta expand a metavariable, if it is of the specified kind. Don't do -- anything if the metavariable is a blocked term. etaExpandMeta :: [MetaKind] -> MetaId -> TCM () -- | Eta expand blocking metavariables of record type, and reduce the -- blocked thing. etaExpandBlocked :: Reduce t => Blocked t -> TCM (Blocked t) -- | Assign to an open metavar which may not be frozen. First check that -- metavar args are in pattern fragment. Then do extended occurs check on -- given thing. -- -- Assignment is aborted by throwing a PatternErr via a call to -- patternViolation. This error is caught by -- catchConstraint during equality checking -- (compareAtom) and leads to restoration of the original -- constraints. assignV :: CompareDirection -> MetaId -> Args -> Term -> TCM () assignWrapper :: CompareDirection -> MetaId -> Elims -> Term -> TCM () -> TCM () -- | Miller pattern unification: -- -- assign x vs v solves problem x vs = v for meta -- x if vs are distinct variables (linearity check) and -- v depends only on these variables and does not contain -- x itself (occurs check). -- -- This is the basic story, but we have added some features: -- --
    --
  1. Pruning.
  2. --
  3. Benign cases of non-linearity.
  4. --
  5. vs may contain record patterns.
  6. --
-- -- For a reference to some of these extensions, read Andreas Abel and -- Brigitte Pientka's TLCA 2011 paper. assign :: CompareDirection -> MetaId -> Args -> Term -> TCM () -- | assignMeta m x t ids u solves x ids = u for meta -- x of type t, where term u lives in a -- context of length m. Precondition: ids is linear. assignMeta :: Int -> MetaId -> Type -> [Int] -> Term -> TCM () -- | assignMeta' m x t ids u solves x = [ids]u for meta -- x of type t, where term u lives in a -- context of length m, and ids is a partial -- substitution. assignMeta' :: Int -> MetaId -> Type -> Int -> SubstCand -> Term -> TCM () -- | Turn the assignment problem _X args <= SizeLt u into -- _X args = SizeLt (_Y args) and constraint _Y args <= -- u. subtypingForSizeLt :: CompareDirection -> MetaId -> MetaVariable -> Type -> Args -> Term -> (Term -> TCM ()) -> TCM () -- | Eta-expand bound variables like z in X (fst z). expandProjectedVars :: (Normalise a, TermLike a, Show a, PrettyTCM a, NoProjectedVar a, Subst a, PrettyTCM b, Subst b) => a -> b -> (a -> b -> TCM c) -> TCM c -- | Eta-expand a de Bruijn index of record type in context and passed -- term(s). etaExpandProjectedVar :: (PrettyTCM a, Subst a) => Int -> a -> TCM c -> (a -> TCM c) -> TCM c -- | Check whether one of the meta args is a projected var. class NoProjectedVar a noProjectedVar :: NoProjectedVar a => a -> Either ProjVarExc () data ProjVarExc ProjVarExc :: Int -> [QName] -> ProjVarExc type FVs = VarSet type SubstCand = [(Nat, Term)] a possibly non-deterministic substitution -- | Turn non-det substitution into proper substitution, if possible. -- Otherwise, raise the error. checkLinearity :: SubstCand -> ExceptT () TCM SubstCand type Res = [(Arg Nat, Term)] -- | Exceptions raised when substitution cannot be inverted. data InvertExcept -- | Cannot recover. CantInvert :: InvertExcept -- | A potentially neutral arg: can't invert, but can try pruning. NeutralArg :: InvertExcept -- | Try to eta-expand var to remove projs. ProjectedVar :: Int -> [QName] -> InvertExcept -- | Check that arguments args to a metavar are in pattern -- fragment. Assumes all arguments already in whnf and eta-reduced. -- Parameters are represented as Vars so checkArgs -- really checks that all args are Vars and returns the -- "substitution" to be applied to the rhs of the equation to solve. (If -- args is considered a substitution, its inverse is returned.) -- -- The returned list might not be ordered. Linearity, i.e., whether the -- substitution is deterministic, has to be checked separately. inverseSubst :: Args -> ExceptT InvertExcept TCM SubstCand -- | Used in giveExpr. updateMeta :: MetaId -> Term -> TCM () -- | Returns every meta-variable occurrence in the given type, except for -- those in Sorts. allMetas :: TermLike a => a -> [MetaId] instance GHC.Show.Show Agda.TypeChecking.MetaVars.MetaKind instance GHC.Enum.Bounded Agda.TypeChecking.MetaVars.MetaKind instance GHC.Enum.Enum Agda.TypeChecking.MetaVars.MetaKind instance GHC.Classes.Eq Agda.TypeChecking.MetaVars.MetaKind instance Agda.TypeChecking.MetaVars.NoProjectedVar Agda.Syntax.Internal.Term instance Agda.TypeChecking.MetaVars.NoProjectedVar a => Agda.TypeChecking.MetaVars.NoProjectedVar (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.MetaVars.NoProjectedVar a => Agda.TypeChecking.MetaVars.NoProjectedVar [a] -- | Generates data used for precise syntax highlighting. module Agda.Interaction.Highlighting.Generate -- | Highlighting levels. data Level -- | Full highlighting. Should only be used after typechecking has -- completed successfully. Full :: Level -- | Highlighting without disambiguation of overloaded constructors. Partial :: Level -- | Generate syntax highlighting information for the given declaration, -- and (if appropriate) print it. If the HighlightingLevel is -- Full, then the state is additionally updated with the -- new highlighting info (in case of a conflict new info takes precedence -- over old info). -- -- The procedure makes use of some of the token highlighting info in -- stTokens (that corresponding to the interval covered by the -- declaration). If the HighlightingLevel is Full, -- then this token highlighting info is additionally removed from -- stTokens. generateAndPrintSyntaxInfo :: Declaration -> Level -> TCM () -- | Generate and return the syntax highlighting information for the tokens -- in the given file. generateTokenInfo :: AbsolutePath -> TCM CompressedFile -- | Same as generateTokenInfo but takes a string instead of a -- filename. generateTokenInfoFromString :: Range -> String -> TCM CompressedFile -- | Prints syntax highlighting info for an error. printErrorInfo :: TCErr -> TCM () -- | Generate highlighting for error. Does something special for -- termination errors. errorHighlighting :: TCErr -> TCM File -- | Generates and prints syntax highlighting information for unsolved -- meta-variables and certain unsolved constraints. printUnsolvedInfo :: TCM () -- | Lispify and print the given highlighting information. printHighlightingInfo :: MonadTCM tcm => HighlightingInfo -> tcm () -- | highlightAsTypeChecked rPre r m runs m and returns -- its result. Additionally, some code may be highlighted: -- -- highlightAsTypeChecked :: MonadTCM tcm => Range -> Range -> tcm a -> tcm a -- | Generates syntax highlighting information for unsolved meta variables. computeUnsolvedMetaWarnings :: TCM File -- | Generates syntax highlighting information for unsolved constraints -- that are not connected to a meta variable. computeUnsolvedConstraints :: TCM File -- | Remember a name disambiguation (during type checking). To be used -- later during syntax highlighting. storeDisambiguatedName :: QName -> TCM () -- | All the properties. tests :: IO Bool -- | Responsible for running all internal tests. module Agda.Tests testSuite :: IO Bool module Agda.TypeChecking.Polarity -- | Infimum on the information lattice. Invariant is bottom -- (dominant for inf), Nonvariant is top (neutral for inf). (/\) :: Polarity -> Polarity -> Polarity -- | Polarity negation, swapping monotone and antitone. neg :: Polarity -> Polarity -- | What is the polarity of a function composition? composePol :: Polarity -> Polarity -> Polarity polFromOcc :: Occurrence -> Polarity -- | Get the next polarity from a list, Invariant if empty. nextPolarity :: [Polarity] -> (Polarity, [Polarity]) -- | Replace Nonvariant by Covariant. (Arbitrary bias, but -- better than Invariant, see issue 1596). purgeNonvariant :: [Polarity] -> [Polarity] -- | Main function of this module. computePolarity :: QName -> TCM () -- | Data and record parameters are used as phantom arguments all over the -- test suite (and possibly in user developments). -- enablePhantomTypes turns Nonvariant parameters to -- Covariant to enable phantoms. enablePhantomTypes :: Defn -> [Polarity] -> [Polarity] -- | Make arguments Invariant if the type of a not-Nonvariant -- later argument depends on it. Also, enable phantom types by turning -- Nonvariant into something else if it is a data/record parameter -- but not a size argument. [See issue 1596] -- -- Precondition: the "phantom" polarity list has the same length as the -- polarity list. dependentPolarity :: Type -> [Polarity] -> [Polarity] -> TCM [Polarity] -- | Check whether a variable is relevant in a type expression, ignoring -- domains of non-variant arguments. relevantInIgnoringNonvariant :: Nat -> Type -> [Polarity] -> TCM Bool -- | Record information that an argument is unused in Relevance. mkUnused :: Relevance -> Relevance -- | Improve Relevance information in a type by polarity -- information. Nonvariant becomes UnusedArg. nonvariantToUnusedArg :: [Polarity] -> Type -> TCM Type -- | Propagate Nonvariant Polarity to Relevance -- information in Args of a defined symbol. nonvariantToUnusedArgInDef :: [Polarity] -> Defn -> Defn nonvariantToUnusedArgInClause :: [Polarity] -> Clause -> Clause -- | Hack for polarity of size indices. As a side effect, this sets the -- positivity of the size index. See -- testsucceedPolaritySizeSucData.agda for a case where this is -- needed. sizePolarity :: QName -> [Polarity] -> TCM [Polarity] -- | checkSizeIndex d np i a checks that constructor target type -- a has form d ps (↑ i) idxs where |ps| = np. -- -- Precondition: a is reduced and of form d ps idxs0. checkSizeIndex :: QName -> Nat -> Nat -> Type -> TCM Bool -- | polarities i a computes the list of polarities of de Bruijn -- index i in syntactic entity a. class HasPolarity a polarities :: HasPolarity a => Nat -> a -> TCM [Polarity] -- | polarity i a computes the polarity of de Bruijn index -- i in syntactic entity a by taking the infimum of all -- polarities. polarity :: HasPolarity a => Nat -> a -> TCM Polarity instance Agda.TypeChecking.Polarity.HasPolarity a => Agda.TypeChecking.Polarity.HasPolarity (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.Polarity.HasPolarity a => Agda.TypeChecking.Polarity.HasPolarity (Agda.Syntax.Internal.Dom a) instance Agda.TypeChecking.Polarity.HasPolarity a => Agda.TypeChecking.Polarity.HasPolarity (Agda.Syntax.Internal.Abs a) instance Agda.TypeChecking.Polarity.HasPolarity a => Agda.TypeChecking.Polarity.HasPolarity [a] instance (Agda.TypeChecking.Polarity.HasPolarity a, Agda.TypeChecking.Polarity.HasPolarity b) => Agda.TypeChecking.Polarity.HasPolarity (a, b) instance Agda.TypeChecking.Polarity.HasPolarity Agda.Syntax.Internal.Type instance Agda.TypeChecking.Polarity.HasPolarity a => Agda.TypeChecking.Polarity.HasPolarity (Agda.Syntax.Internal.Elim' a) instance Agda.TypeChecking.Polarity.HasPolarity Agda.Syntax.Internal.Term instance Agda.TypeChecking.Polarity.HasPolarity Agda.Syntax.Internal.Level instance Agda.TypeChecking.Polarity.HasPolarity Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Polarity.HasPolarity Agda.Syntax.Internal.LevelAtom module Agda.TypeChecking.Rules.LHS.Instantiate -- | Instantiate a telescope with a substitution. Might reorder the -- telescope. instantiateTel (Γ : Tel)(σ : Γ --> Γ) = Γσ~ -- Monadic only for debugging purposes. instantiateTel :: Substitution -> Telescope -> TCM (Telescope, Permutation, Substitution, [Dom Type]) -- | Produce a nice error message when splitting failed nothingToSplitError :: Problem -> TCM a module Agda.TypeChecking.Coverage.Match -- | Given -- --
    --
  1. the function clauses cs
  2. --
  3. the patterns ps and permutation perm of a split -- clause
  4. --
-- -- we want to compute a variable index of the split clause to split on -- next. -- -- First, we find the set cs' of all the clauses that are -- instances (via substitutions rhos) of the split clause. -- -- In these substitutions, we look for a column that has only constructor -- patterns. We try to split on this column first. -- -- Match the given patterns against a list of clauses match :: [Clause] -> [Arg Pattern] -> Permutation -> Match Nat -- | We use a special representation of the patterns we're trying to match -- against a clause. In particular we want to keep track of which -- variables are blocking a match. data MPat -- | De Bruijn index (usually, rightmost variable in patterns is 0). VarMP :: Nat -> MPat ConMP :: ConHead -> [Arg MPat] -> MPat LitMP :: Literal -> MPat -- | For dot patterns that cannot be turned into patterns. WildMP :: MPat -- | Projection copattern. ProjMP :: QName -> MPat buildMPatterns :: Permutation -> [Arg Pattern] -> [Arg MPat] -- | If matching is inconclusive (Block) we want to know which -- variables are blocking the match. data Match a -- | Matches unconditionally. Yes :: a -> Match a -- | Definitely does not match. No :: Match a -- | Could match if non-empty list of blocking variables is instantiated -- properly. Block :: BlockingVars -> Match a -- | Could match if split on possible projections is performed. BlockP :: Match a -- | Variable blocking a match. data BlockingVar BlockingVar :: Nat -> Maybe [ConHead] -> BlockingVar -- | De Bruijn index of variable blocking the match. [blockingVarNo] :: BlockingVar -> Nat -- | Nothing means there is an overlapping match for this -- variable. This happens if one clause has a constructor pattern at this -- position, and another a variable. It is also used for "just variable". -- -- Just cons means that it is an non-overlapping match and -- cons are the encountered constructors. [blockingVarCons] :: BlockingVar -> Maybe [ConHead] type BlockingVars = [BlockingVar] mapBlockingVarCons :: (Maybe [ConHead] -> Maybe [ConHead]) -> BlockingVar -> BlockingVar clearBlockingVarCons :: BlockingVar -> BlockingVar overlapping :: BlockingVars -> BlockingVars -- | Left dominant merge of blocking vars. zipBlockingVars :: BlockingVars -> BlockingVars -> BlockingVars -- | choice m m' combines the match results m of a -- function clause with the (already combined) match results $m'$ of the -- later clauses. It is for skipping clauses that definitely do not match -- (No). It is left-strict, to be used with foldr. If one -- clause unconditionally matches (Yes) we do not look further. choice :: Match a -> Match a -> Match a type MatchLit = Literal -> MPat -> Match () noMatchLit :: MatchLit yesMatchLit :: MatchLit -- | Check if a clause could match given generously chosen literals matchLits :: Clause -> [Arg Pattern] -> Permutation -> Bool -- | matchClause mlit qs i c checks whether clause c -- number i covers a split clause with patterns qs. matchClause :: MatchLit -> [Arg MPat] -> Nat -> Clause -> Match Nat -- | matchPats mlit ps qs checks whether a function clause with -- patterns ps covers a split clause with patterns qs. -- -- Issue 842: if in case of functions with varying arity, the split -- clause has proper patterns left, we refuse to match, because it would -- be troublesome to construct the split tree later. We would have to -- move bindings from the rhs to the lhs. For example, this is rejected: -- F : Bool -> Set1 F true = Set F = x -> Set matchPats :: MatchLit -> [Arg Pattern] -> [Arg MPat] -> Match () -- | Combine results of checking whether function clause patterns covers -- split clause patterns. -- -- No is dominant: if one function clause pattern is disjoint to -- the corresponding split clause pattern, then the whole clauses are -- disjoint. -- -- Yes is neutral: for a match, all patterns have to match. -- -- Block accumulates variables of the split clause that have to be -- instantiated to make the split clause an instance of the function -- clause. -- -- BlockP yields to Block, since blocking vars can also -- block the result type. -- | matchPat mlit p q checks whether a function clause pattern -- p covers a split clause pattern q. There are three -- results: Yes () means it covers, because p is a -- variable pattern or q is a wildcard. No means it -- does not cover. Block [x] means p is a proper -- instance of q and could become a cover if q was -- split on variable x. matchPat :: MatchLit -> Pattern -> MPat -> Match () instance GHC.Base.Functor Agda.TypeChecking.Coverage.Match.Match instance GHC.Show.Show Agda.TypeChecking.Coverage.Match.BlockingVar instance GHC.Base.Monoid a => GHC.Base.Monoid (Agda.TypeChecking.Coverage.Match.Match a) module Agda.TypeChecking.Quote data QuotingKit QuotingKit :: (Term -> ReduceM Term) -> (Type -> ReduceM Term) -> (Clause -> ReduceM Term) -> (Dom Type -> ReduceM Term) -> QuotingKit [quoteTermWithKit] :: QuotingKit -> Term -> ReduceM Term [quoteTypeWithKit] :: QuotingKit -> Type -> ReduceM Term [quoteClauseWithKit] :: QuotingKit -> Clause -> ReduceM Term [quoteDomWithKit] :: QuotingKit -> Dom Type -> ReduceM Term quotingKit :: TCM QuotingKit quoteName :: QName -> Term quoteConName :: ConHead -> Term quoteTerm :: Term -> TCM Term quoteType :: Type -> TCM Term -- | Primitive functions, such as addition on builtin integers. module Agda.TypeChecking.Primitive data PrimitiveImpl PrimImpl :: Type -> PrimFun -> PrimitiveImpl newtype Nat Nat :: Integer -> Nat [unNat] :: Nat -> Integer newtype Lvl Lvl :: Integer -> Lvl [unLvl] :: Lvl -> Integer class PrimType a primType :: PrimType a => a -> TCM Type class PrimTerm a primTerm :: PrimTerm a => a -> TCM Term class ToTerm a where toTermR = (pure .) <$> toTerm toTerm :: ToTerm a => TCM (a -> Term) toTermR :: ToTerm a => TCM (a -> ReduceM Term) -- | buildList A ts builds a list of type List A. Assumes -- that the terms ts all have type A. buildList :: TCM ([Term] -> Term) type FromTermFunction a = Arg Term -> ReduceM (Reduced (MaybeReduced (Arg Term)) a) class FromTerm a fromTerm :: FromTerm a => TCM (FromTermFunction a) -- | Conceptually: redBind m f k = either (return . Left . f) k -- =<< m redBind :: ReduceM (Reduced a a') -> (a -> b) -> (a' -> ReduceM (Reduced b b')) -> ReduceM (Reduced b b') redReturn :: a -> ReduceM (Reduced a' a) fromReducedTerm :: (Term -> Maybe a) -> TCM (FromTermFunction a) fromLiteral :: (Literal -> Maybe a) -> TCM (FromTermFunction a) primTrustMe :: TCM PrimitiveImpl primQNameType :: TCM PrimitiveImpl primQNameDefinition :: TCM PrimitiveImpl primDataConstructors :: TCM PrimitiveImpl mkPrimLevelZero :: TCM PrimitiveImpl mkPrimLevelSuc :: TCM PrimitiveImpl mkPrimLevelMax :: TCM PrimitiveImpl mkPrimFun1TCM :: (FromTerm a, ToTerm b, TermLike b) => TCM Type -> (a -> ReduceM b) -> TCM PrimitiveImpl mkPrimFun1 :: (PrimType a, FromTerm a, PrimType b, ToTerm b) => (a -> b) -> TCM PrimitiveImpl mkPrimFun2 :: (PrimType a, FromTerm a, ToTerm a, PrimType b, FromTerm b, PrimType c, ToTerm c) => (a -> b -> c) -> TCM PrimitiveImpl mkPrimFun4 :: (PrimType a, FromTerm a, ToTerm a, PrimType b, FromTerm b, ToTerm b, PrimType c, FromTerm c, ToTerm c, PrimType d, FromTerm d, PrimType e, ToTerm e) => (a -> b -> c -> d -> e) -> TCM PrimitiveImpl (-->) :: TCM Type -> TCM Type -> TCM Type (.-->) :: TCM Type -> TCM Type -> TCM Type (..-->) :: TCM Type -> TCM Type -> TCM Type garr :: (Relevance -> Relevance) -> TCM Type -> TCM Type -> TCM Type gpi :: ArgInfo -> String -> TCM Type -> TCM Type -> TCM Type hPi :: String -> TCM Type -> TCM Type -> TCM Type nPi :: String -> TCM Type -> TCM Type -> TCM Type varM :: Int -> TCM Term gApply :: Hiding -> TCM Term -> TCM Term -> TCM Term (<@>) :: TCM Term -> TCM Term -> TCM Term (<#>) :: TCM Term -> TCM Term -> TCM Term list :: TCM Term -> TCM Term io :: TCM Term -> TCM Term el :: TCM Term -> TCM Type tset :: TCM Type tSetOmega :: TCM Type tSizeUniv :: TCM Type -- | Abbreviation: argN = Arg defaultArgInfo. argN :: e -> Arg e domN :: e -> Dom e -- | Abbreviation: argH = hide Arg -- defaultArgInfo. argH :: e -> Arg e domH :: e -> Dom e type Op a = a -> a -> a type Fun a = a -> a type Rel a = a -> a -> Bool type Pred a = a -> Bool primitiveFunctions :: Map String (TCM PrimitiveImpl) lookupPrimitiveFunction :: String -> TCM PrimitiveImpl lookupPrimitiveFunctionQ :: QName -> TCM (String, PrimitiveImpl) instance GHC.Classes.Ord Agda.TypeChecking.Primitive.Lvl instance GHC.Classes.Eq Agda.TypeChecking.Primitive.Lvl instance GHC.Real.Real Agda.TypeChecking.Primitive.Nat instance GHC.Enum.Enum Agda.TypeChecking.Primitive.Nat instance GHC.Num.Num Agda.TypeChecking.Primitive.Nat instance GHC.Classes.Ord Agda.TypeChecking.Primitive.Nat instance GHC.Classes.Eq Agda.TypeChecking.Primitive.Nat instance GHC.Real.Integral Agda.TypeChecking.Primitive.Nat instance GHC.Show.Show Agda.TypeChecking.Primitive.Nat instance GHC.Show.Show Agda.TypeChecking.Primitive.Lvl instance (Agda.TypeChecking.Primitive.PrimType a, Agda.TypeChecking.Primitive.PrimType b) => Agda.TypeChecking.Primitive.PrimTerm (a -> b) instance Agda.TypeChecking.Primitive.PrimTerm a => Agda.TypeChecking.Primitive.PrimType a instance Agda.TypeChecking.Primitive.PrimTerm GHC.Integer.Type.Integer instance Agda.TypeChecking.Primitive.PrimTerm GHC.Types.Bool instance Agda.TypeChecking.Primitive.PrimTerm GHC.Types.Char instance Agda.TypeChecking.Primitive.PrimTerm GHC.Types.Double instance Agda.TypeChecking.Primitive.PrimTerm Agda.Utils.String.Str instance Agda.TypeChecking.Primitive.PrimTerm Agda.TypeChecking.Primitive.Nat instance Agda.TypeChecking.Primitive.PrimTerm Agda.TypeChecking.Primitive.Lvl instance Agda.TypeChecking.Primitive.PrimTerm Agda.Syntax.Abstract.Name.QName instance Agda.TypeChecking.Primitive.PrimTerm Agda.Syntax.Internal.Type instance Agda.TypeChecking.Primitive.PrimTerm a => Agda.TypeChecking.Primitive.PrimTerm [a] instance Agda.TypeChecking.Primitive.PrimTerm a => Agda.TypeChecking.Primitive.PrimTerm (GHC.Types.IO a) instance Agda.TypeChecking.Primitive.ToTerm GHC.Integer.Type.Integer instance Agda.TypeChecking.Primitive.ToTerm Agda.TypeChecking.Primitive.Nat instance Agda.TypeChecking.Primitive.ToTerm Agda.TypeChecking.Primitive.Lvl instance Agda.TypeChecking.Primitive.ToTerm GHC.Types.Double instance Agda.TypeChecking.Primitive.ToTerm GHC.Types.Char instance Agda.TypeChecking.Primitive.ToTerm Agda.Utils.String.Str instance Agda.TypeChecking.Primitive.ToTerm Agda.Syntax.Abstract.Name.QName instance Agda.TypeChecking.Primitive.ToTerm GHC.Types.Bool instance Agda.TypeChecking.Primitive.ToTerm Agda.Syntax.Internal.Term instance Agda.TypeChecking.Primitive.ToTerm Agda.Syntax.Internal.Type instance Agda.TypeChecking.Primitive.ToTerm Agda.Syntax.Internal.ArgInfo instance (Agda.TypeChecking.Primitive.PrimTerm a, Agda.TypeChecking.Primitive.ToTerm a) => Agda.TypeChecking.Primitive.ToTerm [a] instance Agda.TypeChecking.Primitive.FromTerm GHC.Integer.Type.Integer instance Agda.TypeChecking.Primitive.FromTerm Agda.TypeChecking.Primitive.Nat instance Agda.TypeChecking.Primitive.FromTerm Agda.TypeChecking.Primitive.Lvl instance Agda.TypeChecking.Primitive.FromTerm GHC.Types.Double instance Agda.TypeChecking.Primitive.FromTerm GHC.Types.Char instance Agda.TypeChecking.Primitive.FromTerm Agda.Utils.String.Str instance Agda.TypeChecking.Primitive.FromTerm Agda.Syntax.Abstract.Name.QName instance Agda.TypeChecking.Primitive.FromTerm GHC.Types.Bool instance (Agda.TypeChecking.Primitive.ToTerm a, Agda.TypeChecking.Primitive.FromTerm a) => Agda.TypeChecking.Primitive.FromTerm [a] module Agda.TypeChecking.Injectivity headSymbol :: Term -> TCM (Maybe TermHead) checkInjectivity :: QName -> [Clause] -> TCM FunctionInverse -- | Argument should be in weak head normal form. functionInverse :: Term -> TCM InvView data InvView Inv :: QName -> [Elim] -> (Map TermHead Clause) -> InvView NoInv :: InvView data MaybeAbort Abort :: MaybeAbort KeepGoing :: MaybeAbort useInjectivity :: Comparison -> Type -> Term -> Term -> TCM () module Agda.TypeChecking.Conversion -- | Try whether a computation runs without errors or new constraints (may -- create new metas, though). Restores state upon failure. tryConversion :: TCM () -> TCM Bool -- | Try whether a computation runs without errors or new constraints (may -- create new metas, though). Return Just the result upon success. -- Return Nothing and restore state upon failure. tryConversion' :: TCM a -> TCM (Maybe a) -- | Check if to lists of arguments are the same (and all variables). -- Precondition: the lists have the same length. sameVars :: Elims -> Elims -> Bool -- | intersectVars us vs checks whether all relevant elements in -- us and vs are variables, and if yes, returns a prune -- list which says True for arguments which are different and -- can be pruned. intersectVars :: Elims -> Elims -> Maybe [Bool] equalTerm :: Type -> Term -> Term -> TCM () equalAtom :: Type -> Term -> Term -> TCM () equalType :: Type -> Type -> TCM () -- | Ignore errors in irrelevant context. convError :: TypeError -> TCM () -- | Type directed equality on values. compareTerm :: Comparison -> Type -> Term -> Term -> TCM () unifyPointers :: Comparison -> Term -> Term -> TCM () -> TCM () -- | Try to assign meta. If meta is projected, try to eta-expand and run -- conversion check again. assignE :: CompareDirection -> MetaId -> Elims -> Term -> (Term -> Term -> TCM ()) -> TCM () compareTermDir :: CompareDirection -> Type -> Term -> Term -> TCM () compareTerm' :: Comparison -> Type -> Term -> Term -> TCM () -- | compareTel t1 t2 cmp tel1 tel1 checks whether pointwise -- tel1 `cmp` tel2 and complains that t2 `cmp` t1 -- failed if not. compareTel :: Type -> Type -> Comparison -> Telescope -> Telescope -> TCM () -- | Raise UnequalTerms if there is no hope that by meta solving and -- subsequent eta-contraction these terms could become equal. -- Precondition: the terms are in reduced form (with no top-level -- pointer) and failed to be equal in the compareAtom check. -- -- By eta-contraction, a lambda or a record constructor term can become -- anything. etaInequal :: Comparison -> Type -> Term -> Term -> TCM () compareAtomDir :: CompareDirection -> Type -> Term -> Term -> TCM () -- | Syntax directed equality on atomic values compareAtom :: Comparison -> Type -> Term -> Term -> TCM () compareRelevance :: Comparison -> Relevance -> Relevance -> Bool -- | compareElims pols a v els1 els2 performs type-directed -- equality on eliminator spines. t is the type of the head -- v. compareElims :: [Polarity] -> Type -> Term -> [Elim] -> [Elim] -> TCM () -- | Compare two terms in irrelevant position. This always succeeds. -- However, we can dig for solutions of irrelevant metas in the terms we -- compare. (Certainly not the systematic solution, that'd be proof -- search...) compareIrrelevant :: Type -> Term -> Term -> TCM () compareWithPol :: Polarity -> (Comparison -> a -> a -> TCM ()) -> a -> a -> TCM () polFromCmp :: Comparison -> Polarity -- | Type-directed equality on argument lists compareArgs :: [Polarity] -> Type -> Term -> Args -> Args -> TCM () -- | Equality on Types compareType :: Comparison -> Type -> Type -> TCM () leqType :: Type -> Type -> TCM () -- | coerce v a b coerces v : a to type b, -- returning a v' : b with maybe extra hidden applications or -- hidden abstractions. -- -- In principle, this function can host coercive subtyping, but currently -- it only tries to fix problems with hidden function types. coerce :: Term -> Type -> Type -> TCM Term -- | Account for situations like k : (Size< j) <= (Size< k + -- 1) -- -- Actually, the semantics is (Size<= k) ∩ (Size< j) ⊆ rhs -- which gives a disjunctive constraint. Mmmh, looks like stuff TODO. -- -- For now, we do a cheap heuristics. coerceSize :: Term -> Type -> Type -> TCM Term compareLevel :: Comparison -> Level -> Level -> TCM () compareSort :: Comparison -> Sort -> Sort -> TCM () -- | Check that the first sort is less or equal to the second. -- -- We can put SizeUniv below Inf, but otherwise, it is -- unrelated to the other universes. leqSort :: Sort -> Sort -> TCM () leqLevel :: Level -> Level -> TCM () equalLevel :: Level -> Level -> TCM () -- | Check that the first sort equal to the second. equalSort :: Sort -> Sort -> TCM () bothAbsurd :: QName -> QName -> TCM Bool module Agda.TypeChecking.Rules.LHS.Unify -- | Result of unifyIndices. type UnificationResult = UnificationResult' Substitution data UnificationResult' a -- | Unification succeeded. Unifies :: a -> UnificationResult' a -- | Terms are not unifiable. NoUnify :: TCErr -> UnificationResult' a -- | Some other error happened, unification got stuck. DontKnow :: TCErr -> UnificationResult' a -- | Monad for unification. newtype Unify a U :: ReaderT UnifyEnv (WriterT UnifyOutput (ExceptionT UnifyException (StateT UnifyState TCM))) a -> Unify a [unUnify] :: Unify a -> ReaderT UnifyEnv (WriterT UnifyOutput (ExceptionT UnifyException (StateT UnifyState TCM))) a data UnifyMayPostpone MayPostpone :: UnifyMayPostpone MayNotPostpone :: UnifyMayPostpone type UnifyEnv = UnifyMayPostpone emptyUEnv :: UnifyEnv noPostponing :: Unify a -> Unify a askPostpone :: Unify UnifyMayPostpone -- | Output the result of unification (success or maybe). type UnifyOutput = Unifiable -- | Were two terms unifiable or did we have to postpone some equation such -- that we are not sure? data Unifiable -- | Unification succeeded. Definitely :: Unifiable -- | Unification did not fail, but we had to postpone a part. Possibly :: Unifiable -- | Conjunctive monoid. -- | Tell that something could not be unified right now, so the unification -- succeeds only Possibly. reportPostponing :: Unify () -- | Check whether unification proceeded without postponement. ifClean :: Unify () -> Unify a -> Unify a -> Unify a data Equality Equal :: TypeHH -> Term -> Term -> Equality type Sub = IntMap Term data UnifyException ConstructorMismatch :: Type -> Term -> Term -> UnifyException StronglyRigidOccurrence :: Type -> Term -> Term -> UnifyException UnclearOccurrence :: Type -> Term -> Term -> UnifyException WithoutKException :: Type -> Term -> Term -> UnifyException GenericUnifyException :: String -> UnifyException data UnifyState USt :: Sub -> [Equality] -> UnifyState [uniSub] :: UnifyState -> Sub [uniConstr] :: UnifyState -> [Equality] emptyUState :: UnifyState -- | Throw-away error message. projectionMismatch :: QName -> QName -> Unify a constructorMismatch :: Type -> Term -> Term -> Unify a constructorMismatchHH :: TypeHH -> Term -> Term -> Unify a getSub :: Unify Sub modSub :: (Sub -> Sub) -> Unify () checkEqualities :: [Equality] -> TCM () -- | Force equality now instead of postponing it using addEquality. checkEquality :: Type -> Term -> Term -> TCM () -- | Try equality. If constraints remain, postpone (enter unsafe mode). -- Heterogeneous equalities cannot be tried nor reawakened, so we can -- throw them away and flag "dirty". checkEqualityHH :: TypeHH -> Term -> Term -> Unify () -- | Check whether heterogeneous situation is really homogeneous. If not, -- give up. forceHom :: TypeHH -> TCM Type -- | Check whether heterogeneous situation is really homogeneous. If not, -- return Nothing. makeHom :: TypeHH -> TCM (Maybe Type) -- | Try to make a possibly heterogeneous term situation homogeneous. tryHom :: TypeHH -> Term -> Term -> TCM TermHH addEquality :: Type -> Term -> Term -> Unify () addEqualityHH :: TypeHH -> Term -> Term -> Unify () takeEqualities :: Unify [Equality] -- | Includes flexible occurrences, metas need to be solved. TODO: relax? -- TODO: later solutions may remove flexible occurences occursCheck :: Nat -> Term -> Type -> Unify () -- | Assignment with preceding occurs check. (|->) :: Nat -> (Term, Type) -> Unify () makeSubstitution :: Sub -> Substitution -- | Apply the current substitution on a term and reduce to weak head -- normal form. class UReduce t ureduce :: UReduce t => t -> Unify t -- | Take a substitution σ and ensure that no variables from the domain -- appear in the targets. The context of the targets is not changed. -- TODO: can this be expressed using makeSubstitution and applySubst? flattenSubstitution :: Substitution -> Substitution -- | Are we in a homogeneous (one type) or heterogeneous (two types) -- situation? data HomHet a -- | homogeneous Hom :: a -> HomHet a -- | heterogeneous Het :: a -> a -> HomHet a isHom :: HomHet a -> Bool fromHom :: HomHet a -> a leftHH :: HomHet a -> a rightHH :: HomHet a -> a type TermHH = HomHet Term type TypeHH = HomHet Type type TelHH = Tele (Dom TypeHH) type TelViewHH = TelV TypeHH type ArgsHH = HomHet Args absAppHH :: SubstHH t tHH => Abs t -> TermHH -> tHH class ApplyHH t applyHH :: ApplyHH t => t -> HomHet Args -> HomHet t substHH :: SubstHH t tHH => TermHH -> t -> tHH -- | substHH u t substitutes u for the 0th variable in -- t. class SubstHH t tHH substUnderHH :: SubstHH t tHH => Nat -> TermHH -> t -> tHH trivialHH :: SubstHH t tHH => t -> tHH -- | Unify indices. -- -- In unifyIndices_ flex a us vs, -- -- a is the type eliminated by us and vs -- (usally the type of a constructor), need not be reduced, -- -- us and vs are the argument lists to unify, -- -- flex is the set of flexible (instantiable) variabes in -- us and vs. -- -- The result is the most general unifier of us and vs. unifyIndices_ :: MonadTCM tcm => FlexibleVars -> Type -> Args -> Args -> tcm Substitution unifyIndices :: MonadTCM tcm => FlexibleVars -> Type -> Args -> Args -> tcm UnificationResult -- | Given the type of a constructor application the corresponding data or -- record type, applied to its parameters (extracted from the given -- type), is returned. -- -- Precondition: The type has to correspond to an application of the -- given constructor. dataOrRecordType :: ConHead -> Type -> TCM (Maybe Type) dataOrRecordType' :: ConHead -> Type -> TCM (Maybe (QName, Type, Args, Args)) -- | Heterogeneous situation. a1 and a2 need to end in -- same datatype/record. dataOrRecordTypeHH :: ConHead -> TypeHH -> TCM (Maybe TypeHH) dataOrRecordTypeHH' :: ConHead -> TypeHH -> TCM (Maybe (QName, Type, HomHet (Args, Args))) -- | Return record type identifier if argument is a record type. isEtaRecordTypeHH :: MonadTCM tcm => TypeHH -> tcm (Maybe (QName, HomHet Args)) -- | Views an expression (pair) as type shape. Fails if not same shape. data ShapeView a PiSh :: (Dom a) -> (Abs a) -> ShapeView a FunSh :: (Dom a) -> a -> ShapeView a -- | data/record DefSh :: QName -> ShapeView a -- | neutral type VarSh :: Nat -> ShapeView a -- | built-in type LitSh :: Literal -> ShapeView a SortSh :: ShapeView a -- | some meta MetaSh :: ShapeView a -- | not a type or not definitely same shape ElseSh :: ShapeView a -- | Return the type and its shape. Expects input in (u)reduced form. shapeView :: Type -> Unify (Type, ShapeView Type) -- | Return the reduced type(s) and the common shape. shapeViewHH :: TypeHH -> Unify (TypeHH, ShapeView TypeHH) -- | telViewUpToHH n t takes off the first n function -- types of t. Takes off all if $n < 0$. telViewUpToHH :: Int -> TypeHH -> Unify TelViewHH instance GHC.Base.Functor Agda.TypeChecking.Rules.LHS.Unify.ShapeView instance (GHC.Classes.Ord a, Agda.TypeChecking.Substitute.Subst a) => GHC.Classes.Ord (Agda.TypeChecking.Rules.LHS.Unify.ShapeView a) instance (GHC.Classes.Eq a, Agda.TypeChecking.Substitute.Subst a) => GHC.Classes.Eq (Agda.TypeChecking.Rules.LHS.Unify.ShapeView a) instance GHC.Show.Show a => GHC.Show.Show (Agda.TypeChecking.Rules.LHS.Unify.ShapeView a) instance Control.Monad.Writer.Class.MonadWriter Agda.TypeChecking.Rules.LHS.Unify.UnifyOutput Agda.TypeChecking.Rules.LHS.Unify.Unify instance Agda.TypeChecking.Monad.Exception.MonadException Agda.TypeChecking.Rules.LHS.Unify.UnifyException Agda.TypeChecking.Rules.LHS.Unify.Unify instance GHC.Base.Applicative Agda.TypeChecking.Rules.LHS.Unify.Unify instance GHC.Base.Functor Agda.TypeChecking.Rules.LHS.Unify.Unify instance Control.Monad.IO.Class.MonadIO Agda.TypeChecking.Rules.LHS.Unify.Unify instance GHC.Base.Monad Agda.TypeChecking.Rules.LHS.Unify.Unify instance Data.Traversable.Traversable Agda.TypeChecking.Rules.LHS.Unify.HomHet instance Data.Foldable.Foldable Agda.TypeChecking.Rules.LHS.Unify.HomHet instance GHC.Base.Functor Agda.TypeChecking.Rules.LHS.Unify.HomHet instance GHC.Classes.Ord a => GHC.Classes.Ord (Agda.TypeChecking.Rules.LHS.Unify.HomHet a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Agda.TypeChecking.Rules.LHS.Unify.HomHet a) instance GHC.Show.Show a => GHC.Show.Show (Agda.TypeChecking.Rules.LHS.Unify.HomHet a) instance Data.Traversable.Traversable Agda.TypeChecking.Rules.LHS.Unify.UnificationResult' instance Data.Foldable.Foldable Agda.TypeChecking.Rules.LHS.Unify.UnificationResult' instance GHC.Base.Functor Agda.TypeChecking.Rules.LHS.Unify.UnificationResult' instance GHC.Show.Show a => GHC.Show.Show (Agda.TypeChecking.Rules.LHS.Unify.UnificationResult' a) instance Agda.TypeChecking.Monad.Base.MonadTCM Agda.TypeChecking.Rules.LHS.Unify.Unify instance Control.Monad.State.Class.MonadState Agda.TypeChecking.Monad.Base.TCState Agda.TypeChecking.Rules.LHS.Unify.Unify instance Control.Monad.Reader.Class.MonadReader Agda.TypeChecking.Monad.Base.TCEnv Agda.TypeChecking.Rules.LHS.Unify.Unify instance Agda.TypeChecking.Monad.Signature.HasConstInfo Agda.TypeChecking.Rules.LHS.Unify.Unify instance GHC.Base.Monoid Agda.TypeChecking.Rules.LHS.Unify.Unifiable instance Agda.Utils.Except.Error Agda.TypeChecking.Rules.LHS.Unify.UnifyException instance Agda.TypeChecking.Substitute.Subst Agda.TypeChecking.Rules.LHS.Unify.Equality instance Agda.TypeChecking.Rules.LHS.Unify.UReduce Agda.Syntax.Internal.Term instance Agda.TypeChecking.Rules.LHS.Unify.UReduce Agda.Syntax.Internal.Type instance Agda.TypeChecking.Rules.LHS.Unify.UReduce t => Agda.TypeChecking.Rules.LHS.Unify.UReduce (Agda.TypeChecking.Rules.LHS.Unify.HomHet t) instance Agda.TypeChecking.Rules.LHS.Unify.UReduce t => Agda.TypeChecking.Rules.LHS.Unify.UReduce (GHC.Base.Maybe t) instance (Agda.TypeChecking.Rules.LHS.Unify.UReduce a, Agda.TypeChecking.Rules.LHS.Unify.UReduce b) => Agda.TypeChecking.Rules.LHS.Unify.UReduce (a, b) instance (Agda.TypeChecking.Rules.LHS.Unify.UReduce a, Agda.TypeChecking.Rules.LHS.Unify.UReduce b, Agda.TypeChecking.Rules.LHS.Unify.UReduce c) => Agda.TypeChecking.Rules.LHS.Unify.UReduce (a, b, c) instance Agda.TypeChecking.Rules.LHS.Unify.UReduce a => Agda.TypeChecking.Rules.LHS.Unify.UReduce (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.Rules.LHS.Unify.UReduce a => Agda.TypeChecking.Rules.LHS.Unify.UReduce [a] instance Agda.TypeChecking.Substitute.Subst a => Agda.TypeChecking.Substitute.Subst (Agda.TypeChecking.Rules.LHS.Unify.HomHet a) instance Agda.TypeChecking.Pretty.PrettyTCM a => Agda.TypeChecking.Pretty.PrettyTCM (Agda.TypeChecking.Rules.LHS.Unify.HomHet a) instance Agda.TypeChecking.Rules.LHS.Unify.ApplyHH Agda.Syntax.Internal.Term instance Agda.TypeChecking.Rules.LHS.Unify.ApplyHH Agda.Syntax.Internal.Type instance (Agda.TypeChecking.Free.Free a, Agda.TypeChecking.Substitute.Subst a) => Agda.TypeChecking.Rules.LHS.Unify.SubstHH (Agda.TypeChecking.Rules.LHS.Unify.HomHet a) (Agda.TypeChecking.Rules.LHS.Unify.HomHet a) instance Agda.TypeChecking.Rules.LHS.Unify.SubstHH Agda.Syntax.Internal.Term (Agda.TypeChecking.Rules.LHS.Unify.HomHet Agda.Syntax.Internal.Term) instance Agda.TypeChecking.Rules.LHS.Unify.SubstHH Agda.Syntax.Internal.Type (Agda.TypeChecking.Rules.LHS.Unify.HomHet Agda.Syntax.Internal.Type) instance Agda.TypeChecking.Rules.LHS.Unify.SubstHH a b => Agda.TypeChecking.Rules.LHS.Unify.SubstHH (Agda.Syntax.Internal.Arg a) (Agda.Syntax.Internal.Arg b) instance Agda.TypeChecking.Rules.LHS.Unify.SubstHH a b => Agda.TypeChecking.Rules.LHS.Unify.SubstHH (Agda.Syntax.Internal.Dom a) (Agda.Syntax.Internal.Dom b) instance Agda.TypeChecking.Rules.LHS.Unify.SubstHH a b => Agda.TypeChecking.Rules.LHS.Unify.SubstHH (Agda.Syntax.Internal.Abs a) (Agda.Syntax.Internal.Abs b) instance (Agda.TypeChecking.Rules.LHS.Unify.SubstHH a a', Agda.TypeChecking.Rules.LHS.Unify.SubstHH b b') => Agda.TypeChecking.Rules.LHS.Unify.SubstHH (a, b) (a', b') instance Agda.TypeChecking.Rules.LHS.Unify.SubstHH a b => Agda.TypeChecking.Rules.LHS.Unify.SubstHH (Agda.Syntax.Internal.Tele a) (Agda.Syntax.Internal.Tele b) module Agda.Compiler.Epic.Forcing -- | Returns how many parameters a datatype has dataParameters :: QName -> Compile TCM Nat -- | Returns how many parameters a datatype has dataParametersTCM :: QName -> TCM Nat report :: Int -> TCM Doc -> Compile TCM () piApplyM' :: Type -> Args -> TCM Type -- | insertTele i xs t tele tpos tele := Gamma ; (i : T as) ; Delta n := -- parameters T xs' := xs apply (take n as) becomes tpos ( Gamma ; -- xs' ; Delta[i := t] --note that Delta still reference Gamma correctly -- , T as ^ (size xs') ) -- -- we raise the type since we have added xs' new bindings before Gamma, -- and as can only bind to Gamma. insertTele :: (QName, Args) -> Int -> Maybe Type -> Term -> Telescope -> Compile TCM (Telescope, (Telescope, Type, Type)) mkCon :: QName -> Int -> Term unifyI :: Telescope -> FlexibleVars -> Type -> Args -> Args -> Compile TCM [Maybe Term] takeTele :: Int -> Telescope -> Telescope -- | Main function for removing pattern matching on forced variables remForced :: [Fun] -> Compile TCM [Fun] -- | For a given expression, in a certain telescope (the list of Var) is a -- mapping of variable name to the telescope. forcedExpr :: [Var] -> Telescope -> Expr -> Compile TCM Expr -- | replace the forcedVar with pattern matching from the outside. replaceForced :: ([Var], [Var]) -> Telescope -> [Var] -> [Maybe Term] -> Expr -> Compile TCM Expr -- | Given a term containg the forced var, dig out the variable by -- inserting the proper case-expressions. buildTerm :: Var -> Nat -> Term -> Compile TCM (Expr -> Expr, Var) -- | Find the location where a certain Variable index is by searching the -- constructors aswell. i.e find a term that can be transformed into a -- pattern that contains the same value the index. This fails if no such -- term is present. findPosition :: Nat -> [Maybe Term] -> Compile TCM (Maybe (Nat, Term)) -- | A bidirectional type checker for internal syntax. -- -- Performs checking on unreduced terms. With the exception that -- projection-like function applications have to be reduced since they -- break bidirectionality. module Agda.TypeChecking.CheckInternal -- | Entry point for e.g. checking WithFunctionType. checkType :: Type -> TCM () -- | Entry point for term checking. checkInternal :: Term -> Type -> TCM () -- | Infer type of a neutral term. infer :: Term -> TCM Type -- | A constructor argument is forced if it appears as pattern variable in -- an index of the target. -- -- For instance x is forced in sing and n is -- forced in zero and suc: -- --
--   data Sing {a}{A : Set a} : A -> Set where
--     sing : (x : A) -> Sing x
--   
--   data Fin : Nat -> Set where
--     zero : (n : Nat) -> Fin (suc n)
--     suc  : (n : Nat) (i : Fin n) -> Fin (suc n)
--   
-- -- At runtime, forced constructor arguments may be erased as they can be -- recovered from dot patterns. In the epic backend, unsing : {A : -- Set} (x : A) -> Sing x -> A unsing .x (sing x) = x becomes -- unsing x sing = x and proj : (n : Nat) (i : Fin n) -- -> Nat proj .(suc n) (zero n) = n proj .(suc n) (suc n i) = n -- becomes proj (suc n) zero = n proj (suc n) (suc i) = n -- -- Forcing is a concept from pattern matching and thus builds on the -- concept of equality (I) used there (closed terms, extensional) which -- is different from the equality (II) used in conversion checking and -- the constraint solver (open terms, intensional). -- -- Up to issue 1441 (Feb 2015), the forcing analysis here relied on the -- wrong equality (II), considering type constructors as injective. This -- is unsound for Epic's program extraction, but ok if forcing is only -- used to decide which arguments to skip during conversion checking. -- -- From now on, forcing uses equality (I) and does not search for forced -- variables under type constructors. This may lose some savings during -- conversion checking. If this turns out to be a problem, the old -- forcing could be brought back, using a new modality Skip to -- indicate that this is a relevant argument but still can be skipped -- during conversion checking as it is forced by equality (II). module Agda.TypeChecking.Forcing -- | Given the type of a constructor (excluding the parameters), decide -- which arguments are forced. Update the relevance info in the domains -- accordingly. Precondition: the type is of the form Γ → D vs -- and the vs are in normal form. addForcingAnnotations :: Type -> TCM Type -- | Compute the pattern variables of a term or term-like thing. class ForcedVariables a forcedVariables :: ForcedVariables a => a -> [Nat] -- | Assumes that the term is in normal form. -- | force s xs t marks the domains xs in function type -- t as forced. Domains bigger than s are marked as -- Forced Big, others as Forced -- Small. Counting left-to-right, starting with 0. -- Precondition: function type is exposed. force :: Sort -> [Nat] -> Type -> TCM Type instance (Agda.TypeChecking.Forcing.ForcedVariables a, Data.Foldable.Foldable t) => Agda.TypeChecking.Forcing.ForcedVariables (t a) instance Agda.TypeChecking.Forcing.ForcedVariables Agda.Syntax.Internal.Term -- | Rewriting with arbitrary rules. -- -- The user specifies a relation symbol by the pragma {--} -- where rel should be of type Δ → (lhs rhs : A) → Set -- i. -- -- Then the user can add rewrite rules by the pragma {--} -- where q should be a closed term of type Γ → rel us lhs -- rhs. -- -- We then intend to add a rewrite rule Γ ⊢ lhs ↦ rhs : B to -- the signature where B = A[us/Δ]. -- -- To this end, we normalize lhs, which should be of the form -- f ts for a Def-symbol f (postulate, -- function, data, record, constructor). Further, FV(ts) = -- dom(Γ). The rule q :: Γ ⊢ f ts ↦ rhs : B is added to the -- signature to the definition of f. -- -- When reducing a term Ψ ⊢ f vs is stuck, we try the rewrites -- for f, by trying to unify vs with ts. This -- is for now done by substituting fresh metas Xs for the bound variables -- in ts and checking equality with vs Ψ ⊢ (f -- ts)[XsΓ] = f vs : B[XsΓ] If successful (no open -- metas/constraints), we replace f vs by rhs[Xs/Γ] and -- continue reducing. module Agda.TypeChecking.Rewriting requireOptionRewriting :: TCM () -- | Check that the name given to the BUILTIN REWRITE is actually a -- relation symbol. I.e., its type should be of the form Δ → (lhs rhs -- : A) → Set ℓ. Note: we do not care about hiding/non-hiding of lhs -- and rhs. verifyBuiltinRewrite :: Term -> Type -> TCM () -- | Deconstructing a type into Δ → t → t' → core. data RelView RelView :: Telescope -> ListTel -> Type -> Type -> Type -> RelView -- | The whole telescope Δ, t, t'. [relViewTel] :: RelView -> Telescope -- | Δ. [relViewDelta] :: RelView -> ListTel -- | t. [relViewType] :: RelView -> Type -- | t'. [relViewType'] :: RelView -> Type -- | core. [relViewCore] :: RelView -> Type -- | Deconstructing a type into Δ → t → t' → core. Returns -- Nothing if not enough argument types. relView :: Type -> TCM (Maybe RelView) -- | Add q : Γ → rel us lhs rhs as rewrite rule Γ ⊢ lhs ↦ rhs -- : B to the signature where B = A[us/Δ]. Remember that -- rel : Δ → A → A → Set i, so rel us : (lhs rhs : A[us/Δ]) -- → Set i. -- -- Makes only sense in empty context. addRewriteRule :: QName -> TCM () -- | Append rewrite rules to a definition. addRewriteRules :: QName -> RewriteRules -> TCM () -- | rewriteWith t v rew tries to rewrite v : t with -- rew, returning the reduct if successful. rewriteWith :: Maybe Type -> Term -> RewriteRule -> ReduceM (Either (Blocked Term) Term) -- | rewrite t tries to rewrite a reduced term. rewrite :: Blocked Term -> ReduceM (Either (Blocked Term) Term) class NLPatVars a nlPatVars :: NLPatVars a => a -> IntSet rewArity :: RewriteRule -> Int instance (Data.Foldable.Foldable f, Agda.TypeChecking.Rewriting.NLPatVars a) => Agda.TypeChecking.Rewriting.NLPatVars (f a) instance Agda.TypeChecking.Rewriting.NLPatVars Agda.TypeChecking.Monad.Base.NLPat -- | Solving size constraints under hypotheses. -- -- The size solver proceeds as follows: -- --
    --
  1. Get size constraints, cluster into connected components.
  2. --
-- -- All size constraints that mention the same metas go into the same -- cluster. Each cluster can be solved by itself. -- -- Constraints that do not fit our format are ignored. We check whether -- our computed solution fulfills them as well in the last step. -- --
    --
  1. Find a joint context for each cluster.
  2. --
-- -- Each constraint comes with its own typing context, which contains size -- hypotheses j : Size< i. We need to find a common super -- context in which all constraints of a cluster live, and raise all -- constraints to this context. -- -- This involves migrating from de Bruijn indices to de Bruijn levels. -- -- There might not be a common super context. Then we are screwed, since -- our solver is not ready to deal with such a situation. We will -- blatantly refuse to solve this cluster and blame it on the user. -- --
    --
  1. Convert the joint context into a hypothesis graph.
  2. --
-- -- This is straightforward. Each de Bruijn level becomes a rigid -- variable, each typing assumption j : Size< i becomes an -- arc. -- --
    --
  1. Convert the constraints into a constraint graph.
  2. --
-- -- Here we need to convert MetaVs into flexible variables. -- --
    --
  1. Run the solver
  2. --
  3. Convert the solution into meta instantiations.
  4. --
  5. Double-check whether the constraints are solved.
  6. --
module Agda.TypeChecking.SizedTypes.Solve -- | Solve size constraints involving hypotheses. solveSizeConstraints :: TCM () solveSizeConstraints_ :: [Closure Constraint] -> TCM () solveCluster :: [HypSizeConstraint] -> TCM () -- | Collect constraints from a typing context, looking for SIZELT -- hypotheses. getSizeHypotheses :: Context -> TCM [(CtxId, SizeConstraint)] -- | Convert size constraint into form where each meta is applied to -- indices 0,1,..,n-1 where n is the arity of that -- meta. -- -- X[σ] <= t beomes X[id] <= t[σ^-1] -- -- X[σ] ≤ Y[τ] becomes X[id] ≤ Y[τ[σ^-1]] or -- X[σ[τ^1]] ≤ Y[id] whichever is defined. If none is defined, -- we give up. canonicalizeSizeConstraint :: SizeConstraint -> Maybe (SizeConstraint) -- | Identifiers for rigid variables. data NamedRigid NamedRigid :: String -> Int -> NamedRigid -- | Name for printing in debug messages. [rigidName] :: NamedRigid -> String -- | De Bruijn index. [rigidIndex] :: NamedRigid -> Int -- | Size metas in size expressions. data SizeMeta SizeMeta :: MetaId -> [Int] -> SizeMeta [sizeMetaId] :: SizeMeta -> MetaId [sizeMetaArgs] :: SizeMeta -> [Int] -- | An equality which ignores the meta arguments. -- | An order which ignores the meta arguments. -- | Size expression with de Bruijn indices. type DBSizeExpr = SizeExpr' NamedRigid SizeMeta -- | Only for raise. type SizeConstraint = Constraint' NamedRigid SizeMeta -- | Assumes we are in the right context. -- | Size constraint with de Bruijn indices. data HypSizeConstraint HypSizeConstraint :: Context -> [CtxId] -> [SizeConstraint] -> SizeConstraint -> HypSizeConstraint [sizeContext] :: HypSizeConstraint -> Context [sizeHypIds] :: HypSizeConstraint -> [CtxId] [sizeHypotheses] :: HypSizeConstraint -> [SizeConstraint] [sizeConstraint] :: HypSizeConstraint -> SizeConstraint -- | Turn a constraint over de Bruijn indices into a size constraint. computeSizeConstraint :: Closure Constraint -> TCM (Maybe HypSizeConstraint) -- | Turn a term into a size expression. -- -- Returns Nothing if the term isn't a proper size expression. sizeExpr :: Term -> TCM (Maybe DBSizeExpr) -- | Turn a de size expression into a term. unSizeExpr :: DBSizeExpr -> TCM Term instance GHC.Classes.Eq Agda.TypeChecking.SizedTypes.Solve.NamedRigid instance GHC.Classes.Ord Agda.TypeChecking.SizedTypes.Solve.NamedRigid instance GHC.Show.Show Agda.TypeChecking.SizedTypes.Solve.NamedRigid instance Agda.TypeChecking.SizedTypes.Utils.Plus Agda.TypeChecking.SizedTypes.Solve.NamedRigid GHC.Types.Int Agda.TypeChecking.SizedTypes.Solve.NamedRigid instance GHC.Classes.Eq Agda.TypeChecking.SizedTypes.Solve.SizeMeta instance GHC.Classes.Ord Agda.TypeChecking.SizedTypes.Solve.SizeMeta instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.SizedTypes.Solve.SizeMeta instance Agda.TypeChecking.Substitute.Subst Agda.TypeChecking.SizedTypes.Solve.SizeMeta instance Agda.TypeChecking.Substitute.Subst (Agda.TypeChecking.SizedTypes.Syntax.SizeExpr' Agda.TypeChecking.SizedTypes.Solve.NamedRigid Agda.TypeChecking.SizedTypes.Solve.SizeMeta) instance Agda.TypeChecking.Substitute.Subst Agda.TypeChecking.SizedTypes.Solve.SizeConstraint instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.SizedTypes.Solve.SizeConstraint instance Agda.TypeChecking.SizedTypes.Syntax.Flexs Agda.TypeChecking.SizedTypes.Solve.SizeMeta Agda.TypeChecking.SizedTypes.Solve.HypSizeConstraint instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.SizedTypes.Solve.HypSizeConstraint module Agda.TypeChecking.Rules.Data -- | Type check a datatype definition. Assumes that the type has already -- been checked. checkDataDef :: DefInfo -> QName -> [LamBinding] -> [Constructor] -> TCM () -- | A parameter is small if its sort fits into the data sort. -- smallParams overapproximates the small parameters (in doubt: -- small). smallParams :: Telescope -> Sort -> TCM [Int] -- | Type check a constructor declaration. Checks that the constructor -- targets the datatype and that it fits inside the declared sort. -- Returns the non-linear parameters. checkConstructor :: QName -> Telescope -> Nat -> Sort -> Constructor -> TCM [Int] -- | Bind the parameters of a datatype. bindParameters :: [LamBinding] -> Type -> (Telescope -> Type -> TCM a) -> TCM a -- | Check that the arguments to a constructor fits inside the sort of the -- datatype. The first argument is the type of the constructor. fitsIn :: Type -> Sort -> TCM () -- | Return the parameters that share variables with the indices -- nonLinearParameters :: Int -> Type -> TCM [Int] -- nonLinearParameters nPars t = -- -- Check that a type constructs something of the given datatype. The -- first argument is the number of parameters to the datatype. -- -- As a side effect, return the parameters that occur free in indices. -- E.g. in data Eq (A : Set)(a : A) : A -> Set where refl : Eq A a -- a this would include parameter a, but not A. -- -- TODO: what if there's a meta here? constructs :: Int -> Type -> QName -> TCM [Int] -- | Is the type coinductive? Returns Nothing if the answer cannot -- be determined. isCoinductive :: Type -> TCM (Maybe Bool) module Agda.TypeChecking.Unquote agdaTermType :: TCM Type qNameType :: TCM Type type UnquoteM = ExceptionT UnquoteError TCM runUnquoteM :: UnquoteM a -> TCM (Either UnquoteError a) isCon :: ConHead -> TCM Term -> UnquoteM Bool class Unquote a unquote :: Unquote a => Term -> UnquoteM a unquoteH :: Unquote a => Arg Term -> UnquoteM a unquoteN :: Unquote a => Arg Term -> UnquoteM a choice :: Monad m => [(m Bool, m a)] -> m a -> m a ensureDef :: QName -> UnquoteM QName ensureCon :: QName -> UnquoteM QName pickName :: Type -> String data UnquotedFunDef UnQFun :: Type -> [Clause] -> UnquotedFunDef reifyUnquoted :: Reify a e => a -> TCM e instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Internal.ArgInfo instance Agda.TypeChecking.Unquote.Unquote a => Agda.TypeChecking.Unquote.Unquote (Agda.Syntax.Internal.Arg a) instance Agda.TypeChecking.Unquote.Unquote a => Agda.TypeChecking.Unquote.Unquote (Agda.Syntax.Internal.Elim' a) instance Agda.TypeChecking.Unquote.Unquote GHC.Integer.Type.Integer instance Agda.TypeChecking.Unquote.Unquote GHC.Types.Double instance Agda.TypeChecking.Unquote.Unquote GHC.Types.Char instance Agda.TypeChecking.Unquote.Unquote Agda.Utils.String.Str instance Agda.TypeChecking.Unquote.Unquote a => Agda.TypeChecking.Unquote.Unquote [a] instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Common.Hiding instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Common.Relevance instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Abstract.Name.QName instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Internal.ConHead instance Agda.TypeChecking.Unquote.Unquote a => Agda.TypeChecking.Unquote.Unquote (Agda.Syntax.Internal.Abs a) instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Internal.Level instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Internal.Type instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Literal.Literal instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Internal.Term instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Internal.Pattern instance Agda.TypeChecking.Unquote.Unquote Agda.Syntax.Internal.Clause instance Agda.TypeChecking.Unquote.Unquote Agda.TypeChecking.Unquote.UnquotedFunDef module Agda.TypeChecking.Rules.LHS.ProblemRest -- | Rename the variables in a telescope using the names from a given -- pattern useNamesFromPattern :: [NamedArg Pattern] -> Telescope -> Telescope -- | Are there any untyped user patterns left? noProblemRest :: Problem -> Bool -- | Construct an initial split Problem from user patterns. -- Example: @ -- -- Case : {A : Set} → Maybe A → Set → Set → Set Case nothing B C = B Case -- (just _) B C = C -- -- sample : {A : Set} (m : Maybe A) → Case m Bool (Maybe A → Bool) sample -- (just a) (just b) = true sample (just a) nothing = false sample -- nothing = true The problem generated for the first clause of -- sample with patterns just a, just b would be: -- problemInPat = ["_", "just a"] problemOutPat = [identity-permutation, -- [A, "m"]] problemTel = [A : Set, m : Maybe A] problemRest = -- restPats = ["just b"] restType = "Case m Bool (Maybe A -> Bool)" @ problemFromPats :: [NamedArg Pattern] -> Type -> TCM Problem -- | Try to move patterns from the problem rest into the problem. Possible -- if type of problem rest has been updated to a function type. updateProblemRest_ :: Problem -> TCM (Nat, Problem) updateProblemRest :: LHSState -> TCM LHSState module Agda.TypeChecking.Rules.LHS.Split -- | Split a problem at the first constructor pattern which is actually of -- datatype type. -- -- Or, if there is no constructor pattern left and the rest type is a -- record type and the first rest pattern is a projection pattern, split -- the rest type. -- -- Implicit patterns should have been inserted. splitProblem :: Maybe QName -> Problem -> ListT TCM SplitProblem module Agda.TypeChecking.Rules.LHS -- | Compute the set of flexible patterns in a list of patterns. The result -- is the deBruijn indices of the flexible patterns. flexiblePatterns :: [NamedArg Pattern] -> TCM FlexibleVars -- | A pattern is flexible if it is dotted or implicit, or a record pattern -- with only flexible subpatterns. class IsFlexiblePattern a where isFlexiblePattern p = isJust <$> runMaybeT (maybeFlexiblePattern p) maybeFlexiblePattern :: IsFlexiblePattern a => a -> MaybeT TCM FlexibleVarKind isFlexiblePattern :: IsFlexiblePattern a => a -> TCM Bool -- | Lists of flexible patterns are RecordFlex. -- | Compute the dot pattern instantiations. dotPatternInsts :: [NamedArg Pattern] -> Substitution -> [Dom Type] -> TCM [DotPatternInst] -- | In an internal pattern, replace some pattern variables by dot -- patterns, according to the given substitution. instantiatePattern :: Substitution -> Permutation -> [NamedArg Pattern] -> [NamedArg Pattern] -- | In an internal pattern, replace some pattern variables by dot -- patterns, according to the given substitution. instantiatePattern' :: Substitution -> Permutation -> [NamedArg Pattern] -> [NamedArg Pattern] -- | Check if a problem is solved. That is, if the patterns are all -- variables. isSolvedProblem :: Problem -> Bool -- | For each user-defined pattern variable in the Problem, check -- that the corresponding data type (if any) does not contain a -- constructor of the same name (which is not in scope); this "shadowing" -- could indicate an error, and is not allowed. -- -- Precondition: The problem has to be solved. noShadowingOfConstructors :: Call -> Problem -> TCM () -- | Check that a dot pattern matches it's instantiation. checkDotPattern :: DotPatternInst -> TCM () -- | Bind the variables in a left hand side and check that Hiding of -- the patterns matches the hiding info in the type. -- -- Precondition: the patterns should all be VarP, WildP, or -- AbsurdP and the telescope should have the same size as the -- pattern list. There could also be ConPs resulting from eta -- expanded implicit record patterns. bindLHSVars :: [NamedArg Pattern] -> Telescope -> TCM a -> TCM a -- | Bind as patterns bindAsPatterns :: [AsBinding] -> TCM a -> TCM a -- | Result of checking the LHS of a clause. data LHSResult LHSResult :: Telescope -> [NamedArg Pattern] -> Arg Type -> Permutation -> LHSResult -- | Δ : The types of the pattern variables, in internal dependency order. -- Corresponds to clauseTel. [lhsVarTele] :: LHSResult -> Telescope -- | The patterns in internal syntax. [lhsPatterns] :: LHSResult -> [NamedArg Pattern] -- | The type of the body. Is if Γ is defined. -- Irrelevant to indicate the rhs must be checked in irrelevant -- mode. [lhsBodyType] :: LHSResult -> Arg Type -- | The permutation from pattern vars to Δ. Corresponds to -- clausePerm. [lhsPermutation] :: LHSResult -> Permutation -- | Check a LHS. Main function. -- -- checkLeftHandSide a ps a ret checks that user patterns -- ps eliminate the type a of the defined function, and -- calls continuation ret if successful. checkLeftHandSide :: Call -> Maybe QName -> [NamedArg Pattern] -> Type -> (LHSResult -> TCM a) -> TCM a -- | The loop (tail-recursive): split at a variable in the problem until -- problem is solved checkLHS :: Maybe QName -> LHSState -> TCM LHSState -- | Ensures that we are not performing pattern matching on codata. noPatternMatchingOnCodata :: [NamedArg Pattern] -> TCM () instance Agda.TypeChecking.Rules.LHS.IsFlexiblePattern Agda.Syntax.Abstract.Pattern instance Agda.TypeChecking.Rules.LHS.IsFlexiblePattern (Agda.Syntax.Internal.Pattern' a) instance Agda.TypeChecking.Rules.LHS.IsFlexiblePattern a => Agda.TypeChecking.Rules.LHS.IsFlexiblePattern [a] instance Agda.TypeChecking.Rules.LHS.IsFlexiblePattern a => Agda.TypeChecking.Rules.LHS.IsFlexiblePattern (Agda.Syntax.Common.Arg c a) instance Agda.TypeChecking.Rules.LHS.IsFlexiblePattern a => Agda.TypeChecking.Rules.LHS.IsFlexiblePattern (Agda.Syntax.Common.Named name a) instance Agda.TypeChecking.Reduce.InstantiateFull Agda.TypeChecking.Rules.LHS.LHSResult module Agda.TypeChecking.With -- | Split pattern variables according to with-expressions. splitTelForWith :: Telescope -> Type -> [Type] -> [Term] -> (Telescope, Telescope, Permutation, Type, [Type], [Term]) -- | Abstract with-expressions vs to generate type for with-helper -- function. withFunctionType :: Telescope -> [Term] -> [Type] -> Telescope -> Type -> TCM Type -- | Compute the clauses for the with-function given the original patterns. buildWithFunction :: QName -> QName -> Type -> [NamedArg Pattern] -> Permutation -> Nat -> Nat -> [SpineClause] -> TCM [SpineClause] -- |
--   stripWithClausePatterns parent f t qs π ps = ps'
--   
-- -- -- -- Example: -- --
--   record Stream (A : Set) : Set where
--     coinductive
--     constructor delay
--     field       force : A × Stream A
--   
--   record SEq (s t : Stream A) : Set where
--     coinductive
--     field
--       ~force : let a , as = force s
--                    b , bs = force t
--                in  a ≡ b × SEq as bs
--   
--   test : (s : Nat × Stream Nat) (t : Stream Nat) → SEq (delay s) t → SEq t (delay s)
--   ~force (test (a     , as) t p) with force t
--   ~force (test (suc n , as) t p) | b , bs = {!!}
--   
-- -- With function: -- --
--   f : (t : Stream Nat) (w : Nat × Stream Nat) (a : Nat) (as : Stream Nat)
--       (p : SEq (delay (a , as)) t) → (fst w ≡ a) × SEq (snd w) as
--   
--   Δ  = t a as p   -- reorder to bring with-relevant (= needed) vars first
--   π  = a as t p → Δ
--   qs = (a     , as) t p ~force
--   ps = (suc n , as) t p ~force
--   ps' = (suc n) as t p
--   
-- -- Resulting with-function clause is: -- --
--   f t (b , bs) (suc n) as t p
--   
-- -- Note: stripWithClausePatterns factors ps through qs, -- thus -- --
--   ps = qs[ps']
--   
-- -- where [..] is to be understood as substitution. The -- projection patterns have vanished from ps' (as they are -- already in qs). stripWithClausePatterns :: QName -> QName -> Type -> [NamedArg Pattern] -> Permutation -> [NamedArg Pattern] -> TCM [NamedArg Pattern] -- | Construct the display form for a with function. It will display -- applications of the with function as applications to the original -- function. For instance, -- --
--   aux a b c
--   
--   
-- -- as -- --
--   f (suc a) (suc b) | c
--   
--   
withDisplayForm :: QName -> QName -> Telescope -> Telescope -> Nat -> [NamedArg Pattern] -> Permutation -> Permutation -> TCM DisplayForm patsToElims :: Permutation -> [NamedArg Pattern] -> [Elim' DisplayTerm] -- | Coverage checking, case splitting, and splitting for refine tactics. module Agda.TypeChecking.Coverage data SplitClause SClause :: Telescope -> Permutation -> [NamedArg Pattern] -> Substitution -> Maybe (Arg Type) -> SplitClause -- | Type of variables in scPats. [scTel] :: SplitClause -> Telescope -- | How to get from the variables in the patterns to the telescope. [scPerm] :: SplitClause -> Permutation -- | The patterns leading to the currently considered branch of the split -- tree. [scPats] :: SplitClause -> [NamedArg Pattern] -- | Substitution from scTel to old context. Only needed directly -- after split on variable: * To update scTarget * To rename other -- split variables when splitting on multiple variables. scSubst -- is not `transitive', i.e., does not record the substitution -- from the original context to scTel over a series of splits. It -- is freshly computed after each split by computeNeighborhood; -- also splitResult, which does not split on a variable, should -- reset it to the identity idS, lest it be applied to -- scTarget again, leading to Issue 1294. [scSubst] :: SplitClause -> Substitution -- | The type of the rhs, living in context scTel. This invariant is -- broken before calls to fixTarget; there, scTarget lives -- in the old context. fixTarget moves scTarget to the new -- context by applying substitution scSubst. [scTarget] :: SplitClause -> Maybe (Arg Type) -- | Create a split clause from a clause in internal syntax. clauseToSplitClause :: Clause -> SplitClause -- | Update the target type, add more patterns to split clause if target -- becomes a function type. Returns the domains of the function type (if -- any). fixTarget :: SplitClause -> TCM (Telescope, SplitClause) -- | A Covering is the result of splitting a SplitClause. data Covering Covering :: Nat -> [(QName, SplitClause)] -> Covering -- | De Bruijn level of argument we split on. [covSplitArg] :: Covering -> Nat -- | Covering clauses, indexed by constructor these clauses share. [covSplitClauses] :: Covering -> [(QName, SplitClause)] -- | Project the split clauses out of a covering. splitClauses :: Covering -> [SplitClause] -- | Top-level function for checking pattern coverage. coverageCheck :: QName -> Type -> [Clause] -> TCM SplitTree -- | Entry point from Interaction.MakeCase. splitClauseWithAbsurd :: SplitClause -> Nat -> TCM (Either SplitError (Either SplitClause Covering)) -- | Entry point from TypeChecking.Empty and -- Interaction.BasicOps. splitLast CoInductive is used -- in the refine tactics. splitLast :: Induction -> Telescope -> [NamedArg Pattern] -> TCM (Either SplitError Covering) -- |
--   splitResult f sc = return res
--   
-- -- If the target type of sc is a record type, a covering set of -- split clauses is returned (sc extended by all valid -- projection patterns), otherwise res == Nothing. Note that the -- empty set of split clauses is returned if the record has no fields. splitResult :: QName -> SplitClause -> TCM (Maybe Covering) instance Agda.TypeChecking.Pretty.PrettyTCM Agda.TypeChecking.Coverage.SplitClause module Agda.TypeChecking.CompiledClause.Compile -- | Process function clauses into case tree. This involves: 1. Coverage -- checking, generating a split tree. 2. Translation of lhs record -- patterns into rhs uses of projection. Update the split tree. 3. -- Generating a case tree from the split tree. Phases 1. and 2. are -- skipped if Nothing. compileClauses :: Maybe (QName, Type) -> [Clause] -> TCM CompiledClauses -- | Stripped-down version of Clause used in clause compiler. data Cl Cl :: [Arg Pattern] -> ClauseBody -> Cl [clPats] :: Cl -> [Arg Pattern] [clBody] :: Cl -> ClauseBody type Cls = [Cl] compileWithSplitTree :: SplitTree -> Cls -> CompiledClauses compile :: Cls -> CompiledClauses -- | Get the index of the next argument we need to split on. This the -- number of the first pattern that does a match in the first clause. nextSplit :: Cls -> Maybe (Bool, Int) -- | Is is not a variable pattern? And if yes, is it a record pattern? properSplit :: Pattern -> Maybe Bool -- | Is this a variable pattern? -- -- Maintain invariant: isVar = isNothing . properSplit! isVar :: Pattern -> Bool -- | splitOn single n cs will force expansion of catch-alls if -- single. splitOn :: Bool -> Int -> Cls -> Case Cls splitC :: Int -> Cl -> Case Cl -- | Expand catch-alls that appear before actual matches. -- -- Example: -- --
--   true  y
--   x     false
--   false y
--   
-- -- will expand the catch-all x to false. -- -- Catch-alls need also to be expanded if they come before/after a record -- pattern, otherwise we get into trouble when we want to eliminate -- splits on records later. -- -- Another example (see Issue 1650): f (x, (y, z)) true = a f _ -- false = b Split tree: 0 (first argument of f) - 1 (second -- component of the pair) - 3 (last argument of f) -- true -> a - -- false -> b We would like to get the following case tree: -- case 0 of _,_ -> case 1 of _,_ -> case 3 of true -> a; false -- -> b _ -> case 3 of true -> a; false -> b _ -> case 3 -- of true -> a; false -> b expandCatchAlls :: Bool -> Int -> Cls -> Cls substBody :: Int -> Int -> Term -> ClauseBody -> ClauseBody instance GHC.Show.Show Agda.TypeChecking.CompiledClause.Compile.Cl instance Agda.Utils.Pretty.Pretty Agda.TypeChecking.CompiledClause.Compile.Cl module Agda.TypeChecking.Empty -- | Check whether a type is empty. This check may be postponed as -- emptiness constraint. isEmptyType :: Range -> Type -> TCM () module Agda.TypeChecking.Rules.Term -- | Check that an expression is a type. isType :: Expr -> Sort -> TCM Type -- | Check that an expression is a type without knowing the sort. isType_ :: Expr -> TCM Type ptsRule :: (LensSort a, LensSort b) => a -> b -> TCM Sort -- | Ensure that a (freshly created) function type does not inhabit -- SizeUniv. Precondition: When noFunctionsIntoSize t -- tBlame is called, we are in the context of tBlame in -- order to print it correctly. Not being in context of t should -- not matter, as we are only checking whether its sort reduces to -- SizeUniv. noFunctionsIntoSize :: Type -> Type -> TCM () -- | Check that an expression is a type which is equal to a given type. isTypeEqualTo :: Expr -> Type -> TCM Type leqType_ :: Type -> Type -> TCM () -- | Type check a (module) telescope. Binds the variables defined by the -- telescope. checkTelescope :: Telescope -> (Telescope -> TCM a) -> TCM a -- | Type check the telescope of a dependent function type. Binds the -- resurrected variables defined by the telescope. The returned telescope -- is unmodified (not resurrected). checkPiTelescope :: Telescope -> (Telescope -> TCM a) -> TCM a -- | Flag to control resurrection on domains. data LamOrPi -- | We are checking a module telescope. We pass into the type world to -- check the domain type. This resurrects the whole context. LamNotPi :: LamOrPi -- | We are checking a telescope in a Pi-type. We stay in the term world, -- but add resurrected domains to the context to check the remaining -- domains and codomain of the Pi-type. PiNotLam :: LamOrPi -- | Type check a telescope. Binds the variables defined by the telescope. checkTelescope' :: LamOrPi -> Telescope -> (Telescope -> TCM a) -> TCM a -- | Check a typed binding and extends the context with the bound -- variables. The telescope passed to the continuation is valid in the -- original context. -- -- Parametrized by a flag wether we check a typed lambda or a Pi. This -- flag is needed for irrelevance. checkTypedBindings :: LamOrPi -> TypedBindings -> (Telescope -> TCM a) -> TCM a checkTypedBinding :: LamOrPi -> ArgInfo -> TypedBinding -> (ListTel -> TCM a) -> TCM a -- | Type check a lambda expression. checkLambda :: Arg TypedBinding -> Expr -> Type -> TCM Term -- | Checking a lambda whose domain type has already been checked. checkPostponedLambda :: Arg ([WithHiding Name], Maybe Type) -> Expr -> Type -> TCM Term -- | Insert hidden lambda until the hiding info of the domain type matches -- the expected hiding info. Throws WrongHidingInLambda insertHiddenLambdas :: Hiding -> Type -> (MetaId -> Type -> TCM Term) -> (Type -> TCM Term) -> TCM Term -- | checkAbsurdLambda i h e t checks absurd lambda against type -- t. Precondition: e = AbsurdLam i h checkAbsurdLambda :: ExprInfo -> Hiding -> Expr -> Type -> TCM Term -- | checkExtendedLambda i di qname cs e t check pattern matching -- lambda. Precondition: e = ExtendedLam i di qname cs checkExtendedLambda :: ExprInfo -> DefInfo -> QName -> [Clause] -> Expr -> Type -> TCM Term -- | checkRecordExpression fs e t checks record construction -- against type t. Precondition e = Rec _ fs. checkRecordExpression :: Assigns -> Expr -> Type -> TCM Term -- | checkRecordUpdate ei recexpr fs e t Precondition e = -- RecUpdate ei recexpr fs. checkRecordUpdate :: ExprInfo -> Expr -> Assigns -> Expr -> Type -> TCM Term checkLiteral :: Literal -> Type -> TCM Term -- | checkArguments' exph r args t0 t k tries checkArguments -- exph args t0 t. If it succeeds, it continues k with the -- returned results. If it fails, it registers a postponed typechecking -- problem and returns the resulting new meta variable. -- -- Checks e := ((_ : t0) args) : t. checkArguments' :: ExpandHidden -> ExpandInstances -> Range -> [NamedArg Expr] -> Type -> Type -> (Args -> Type -> TCM Term) -> TCM Term -- | Type check an expression. checkExpr :: Expr -> Type -> TCM Term -- | checkApplication hd args e t checks an application. -- Precondition: Application hs args = appView e -- -- checkApplication disambiguates constructors (and continues to -- checkConstructorApplication) and resolves pattern synonyms. checkApplication :: Expr -> Args -> Expr -> Type -> TCM Term -- | Turn a domain-free binding (e.g. lambda) into a domain-full one, by -- inserting an underscore for the missing type. domainFree :: ArgInfo -> Name -> LamBinding checkMeta :: (Type -> TCM Term) -> Type -> MetaInfo -> TCM Term inferMeta :: (Type -> TCM Term) -> MetaInfo -> TCM (Args -> Term, Type) -- | Type check a meta variable. If its type is not given, we return its -- type, or a fresh one, if it is a new meta. If its type is given, we -- check that the meta has this type, and we return the same type. checkOrInferMeta :: (Type -> TCM Term) -> Maybe Type -> MetaInfo -> TCM (Term, Type) inferHeadDef :: QName -> TCM (Args -> Term, Type) -- | Infer the type of a head thing (variable, function symbol, or -- constructor). We return a function that applies the head to arguments. -- This is because in case of a constructor we want to drop the -- parameters. inferHead :: Expr -> TCM (Args -> Term, Type) inferDef :: (QName -> Args -> TCM Term) -> QName -> TCM (Term, Type) -- | Check the type of a constructor application. This is easier than a -- general application since the implicit arguments can be inserted -- without looking at the arguments to the constructor. checkConstructorApplication :: Expr -> Type -> ConHead -> [NamedArg Expr] -> TCM Term -- | checkHeadApplication e t hd args checks that e has -- type t, assuming that e has the form hd -- args. The corresponding type-checked term is returned. -- -- If the head term hd is a coinductive constructor, then a -- top-level definition fresh tel = hd args (where the clause is -- delayed) is added, where tel corresponds to the current -- telescope. The returned term is fresh tel. -- -- Precondition: The head hd has to be unambiguous, and there -- should not be any need to insert hidden lambdas. checkHeadApplication :: Expr -> Type -> Expr -> [NamedArg Expr] -> TCM Term traceCallE :: Error e => Call -> ExceptT e TCM r -> ExceptT e TCM r -- | Check a list of arguments: checkArgs args t0 t1 checks that -- t0 = Delta -> t0' and args : Delta. Inserts -- hidden arguments to make this happen. Returns the evaluated arguments -- vs, the remaining type t0' (which should be a -- subtype of t1) and any constraints cs that have to -- be solved for everything to be well-formed. checkArguments :: ExpandHidden -> ExpandInstances -> Range -> [NamedArg Expr] -> Type -> Type -> ExceptT (Args, [NamedArg Expr], Type) TCM (Args, Type) -- | Check that a list of arguments fits a telescope. Inserts hidden -- arguments as necessary. Returns the type-checked arguments and the -- remaining telescope. checkArguments_ :: ExpandHidden -> Range -> [NamedArg Expr] -> Telescope -> TCM (Args, Telescope) -- | Infer the type of an expression. Implemented by checking against a -- meta variable. Except for neutrals, for them a polymorphic type is -- inferred. inferExpr :: Expr -> TCM (Term, Type) inferExpr' :: ExpandHidden -> Expr -> TCM (Term, Type) defOrVar :: Expr -> Bool -- | Used to check aliases f = e. Switches off ExpandLast -- for the checking of top-level application. checkDontExpandLast :: Expr -> Type -> TCM Term -- | Check whether a de Bruijn index is bound by a module telescope. isModuleFreeVar :: Int -> TCM Bool -- | Infer the type of an expression, and if it is of the form {tel} -- -> D vs for some datatype D then insert the hidden -- arguments. Otherwise, leave the type polymorphic. inferExprForWith :: Expr -> TCM (Term, Type) checkLetBindings :: [LetBinding] -> TCM a -> TCM a checkLetBinding :: LetBinding -> TCM a -> TCM a class ConvColor a i convColor :: ConvColor a i => a -> i instance GHC.Show.Show Agda.TypeChecking.Rules.Term.LamOrPi instance GHC.Classes.Eq Agda.TypeChecking.Rules.Term.LamOrPi instance Agda.TypeChecking.Rules.Term.ConvColor Agda.Syntax.Abstract.ArgInfo Agda.Syntax.Internal.ArgInfo instance Agda.TypeChecking.Rules.Term.ConvColor (Agda.Syntax.Abstract.Arg e) (Agda.Syntax.Internal.Arg e) instance Agda.TypeChecking.Rules.Term.ConvColor (Agda.Syntax.Abstract.Dom e) (Agda.Syntax.Internal.Dom e) instance Agda.TypeChecking.Rules.Term.ConvColor a i => Agda.TypeChecking.Rules.Term.ConvColor [a] [i] module Agda.TypeChecking.Rules.Builtin -- | Bind a builtin thing to an expression. bindBuiltin :: String -> Expr -> TCM () -- | Bind a builtin thing to a new name. bindBuiltinNoDef :: String -> QName -> TCM () -- | bindPostulatedName builtin e m checks that e is a -- postulated name q, and binds the builtin builtin to -- the term m q def, where def is the current -- Definition of q. bindPostulatedName :: String -> Expr -> (QName -> Definition -> TCM Term) -> TCM () -- | Handling of the INFINITY, SHARP and FLAT builtins. module Agda.TypeChecking.Rules.Builtin.Coinduction -- | The type of . typeOfInf :: TCM Type -- | The type of ♯_. typeOfSharp :: TCM Type -- | The type of . typeOfFlat :: TCM Type -- | Binds the INFINITY builtin, but does not change the type's definition. bindBuiltinInf :: Expr -> TCM () -- | Binds the SHARP builtin, and changes the definitions of INFINITY and -- SHARP. bindBuiltinSharp :: Expr -> TCM () -- | Binds the FLAT builtin, and changes its definition. bindBuiltinFlat :: Expr -> TCM () module Agda.TypeChecking.Rules.Record -- |
--   checkRecDef i name con ps contel fields
--   
-- -- checkRecDef :: DefInfo -> QName -> Maybe (Ranged Induction) -> Maybe QName -> [LamBinding] -> Expr -> [Field] -> TCM () -- | checkRecordProjections m r q tel ftel fs. -- -- checkRecordProjections :: ModuleName -> QName -> ConHead -> Telescope -> Telescope -> [Declaration] -> TCM () module Agda.TypeChecking.Rules.Def checkFunDef :: Delayed -> DefInfo -> QName -> [Clause] -> TCM () -- | A single clause without arguments and without type signature is an -- alias. isAlias :: [Clause] -> Type -> Maybe (Expr, MetaId) -- | Check a trivial definition of the form f = e checkAlias :: Type -> ArgInfo -> Delayed -> DefInfo -> QName -> Expr -> TCM () -- | Type check a definition by pattern matching. checkFunDef' :: Type -> ArgInfo -> Delayed -> Maybe ExtLamInfo -> Maybe QName -> DefInfo -> QName -> [Clause] -> TCM () -- | Set funTerminates according to termination info in -- TCEnv, which comes from a possible termination pragma. useTerPragma :: Definition -> TCM Definition -- | Insert some patterns in the in with-clauses LHS of the given RHS insertPatterns :: [Pattern] -> RHS -> RHS -- | Parameters for creating a with-function. data WithFunctionProblem NoWithFunction :: WithFunctionProblem WithFunction :: QName -> QName -> Type -> Telescope -> Telescope -> [Term] -> [Type] -> Type -> [NamedArg Pattern] -> Permutation -> Permutation -> Permutation -> [Clause] -> WithFunctionProblem -- | Parent function name. [wfParentName] :: WithFunctionProblem -> QName -- | With function name. [wfName] :: WithFunctionProblem -> QName -- | Type of the parent function. [wfParentType] :: WithFunctionProblem -> Type -- | Types of arguments to the with function before the with expressions -- (needed vars). [wfBeforeTel] :: WithFunctionProblem -> Telescope -- | Types of arguments to the with function after the with expressions -- (unneeded vars). [wfAfterTel] :: WithFunctionProblem -> Telescope -- | With expressions. [wfExprs] :: WithFunctionProblem -> [Term] -- | Types of the with expressions. [wfExprTypes] :: WithFunctionProblem -> [Type] -- | Type of the right hand side. [wfRHSType] :: WithFunctionProblem -> Type -- | Parent patterns. [wfParentPats] :: WithFunctionProblem -> [NamedArg Pattern] -- | Permutation resulting from splitting the telescope into needed and -- unneeded vars. [wfPermSplit] :: WithFunctionProblem -> Permutation -- | Permutation reordering the variables in the parent pattern. [wfPermParent] :: WithFunctionProblem -> Permutation -- | Final permutation (including permutation for the parent clause). [wfPermFinal] :: WithFunctionProblem -> Permutation -- | The given clauses for the with function [wfClauses] :: WithFunctionProblem -> [Clause] -- | Create a clause body from a term. -- -- As we have type checked the term in the clause telescope, but the -- final body should have bindings in the order of the pattern variables, -- we need to apply the permutation to the checked term. mkBody :: Permutation -> Term -> ClauseBody -- | Type check a function clause. checkClause :: Type -> SpineClause -> TCM Clause -- | Type check the with and rewrite lhss and/or the rhs. checkRHS :: LHSInfo -> QName -> [NamedArg Pattern] -> Type -> LHSResult -> RHS -> TCM (ClauseBody, WithFunctionProblem) checkWithFunction :: WithFunctionProblem -> TCM () -- | Type check a where clause. checkWhere :: Type -> [Declaration] -> TCM a -> TCM a -- | Check if a pattern contains an absurd pattern. For instance, suc -- () containsAbsurdPattern :: Pattern -> Bool module Agda.TypeChecking.Rules.Decl -- | Type check a sequence of declarations. checkDecls :: [Declaration] -> TCM () -- | Type check a single declaration. checkDecl :: Declaration -> TCM () mutualChecks :: MutualInfo -> Declaration -> [Declaration] -> Set QName -> TCM () type FinalChecks = Maybe (TCM ()) checkUnquoteDecl :: MutualInfo -> DefInfo -> QName -> Expr -> TCM FinalChecks -- | Instantiate all metas in Definition associated to QName. -- -- Makes sense after freezing metas. Some checks, like free variable -- analysis, are not in TCM, -- so they will be more precise (see -- issue 1099) after meta instantiation. -- Precondition: name has been -- added to signature already. instantiateDefinitionType :: QName -> TCM () -- | Highlight a declaration. highlight_ :: Declaration -> TCM () -- | Termination check a declaration. checkTermination_ :: Declaration -> TCM () -- | Check a set of mutual names for positivity. checkPositivity_ :: Set QName -> TCM () -- | Check that all coinductive records are actually recursive. (Otherwise, -- one can implement invalid recursion schemes just like for the old -- coinduction.) checkCoinductiveRecords :: [Declaration] -> TCM () -- | Check a set of mutual names for constructor-headedness. checkInjectivity_ :: Set QName -> TCM () -- | Check a set of mutual names for projection likeness. -- -- Only a single, non-abstract function can be projection-like. Making an -- abstract function projection-like would break the invariant that the -- type of the principle argument of a projection-like function is always -- inferable. checkProjectionLikeness_ :: Set QName -> TCM () -- | Type check an axiom. checkAxiom :: Axiom -> DefInfo -> ArgInfo -> QName -> Expr -> TCM () -- | Type check a primitive function declaration. checkPrimitive :: DefInfo -> QName -> Expr -> TCM () -- | Check a pragma. checkPragma :: Range -> Pragma -> TCM () -- | Type check a bunch of mutual inductive recursive definitions. -- -- All definitions which have so far been assigned to the given mutual -- block are returned. checkMutual :: MutualInfo -> [Declaration] -> TCM (Set QName) -- | Type check the type signature of an inductive or recursive definition. checkTypeSignature :: TypeSignature -> TCM () -- | Type check a module. checkSection :: ModuleInfo -> ModuleName -> Telescope -> [Declaration] -> TCM () -- | Helper for checkSectionApplication. -- -- Matches the arguments of the module application with the module -- parameters. -- -- Returns the remaining module parameters as an open telescope. Warning: -- the returned telescope is not the final result, an actual -- instantiation of the parameters does not occur. checkModuleArity :: ModuleName -> Telescope -> [NamedArg Expr] -> TCM Telescope -- | Check an application of a section (top-level function, includes -- traceCall). checkSectionApplication :: ModuleInfo -> ModuleName -> ModuleApplication -> Ren QName -> Ren ModuleName -> TCM () -- | Check an application of a section. checkSectionApplication' :: ModuleInfo -> ModuleName -> ModuleApplication -> Ren QName -> Ren ModuleName -> TCM () -- | Type check an import declaration. Actually doesn't do anything, since -- all the work is done when scope checking. checkImport :: ModuleInfo -> ModuleName -> TCM () class ShowHead a showHead :: ShowHead a => a -> String debugPrintDecl :: Declaration -> TCM () instance Agda.TypeChecking.Rules.Decl.ShowHead Agda.Syntax.Abstract.Declaration module Agda.TheTypeChecker -- | Type check a sequence of declarations. checkDecls :: [Declaration] -> TCM () -- | Type check a single declaration. checkDecl :: Declaration -> TCM () -- | Infer the type of an expression. Implemented by checking against a -- meta variable. Except for neutrals, for them a polymorphic type is -- inferred. inferExpr :: Expr -> TCM (Term, Type) -- | Type check an expression. checkExpr :: Expr -> Type -> TCM Term module Agda.Interaction.BasicOps -- | Parses an expression. parseExpr :: Range -> String -> TCM Expr parseExprIn :: InteractionId -> Range -> String -> TCM Expr giveExpr :: MetaId -> Expr -> TCM Expr -- | Try to fill hole by expression. -- -- Returns the given expression unchanged (for convenient generalization -- to refine). give :: InteractionId -> Maybe Range -> Expr -> TCM Expr -- | Try to refine hole by expression e. -- -- This amounts to successively try to give e, e ?, -- e ? ?, ... Returns the successfully given expression. refine :: InteractionId -> Maybe Range -> Expr -> TCM Expr -- | Evaluate the given expression in the current environment evalInCurrent :: Expr -> TCM Expr evalInMeta :: InteractionId -> Expr -> TCM Expr data Rewrite AsIs :: Rewrite Instantiated :: Rewrite HeadNormal :: Rewrite Simplified :: Rewrite Normalised :: Rewrite normalForm :: Rewrite -> Type -> TCM Type data OutputForm a b OutputForm :: Range -> ProblemId -> (OutputConstraint a b) -> OutputForm a b data OutputConstraint a b OfType :: b -> a -> OutputConstraint a b CmpInType :: Comparison -> a -> b -> b -> OutputConstraint a b CmpElim :: [Polarity] -> a -> [b] -> [b] -> OutputConstraint a b JustType :: b -> OutputConstraint a b CmpTypes :: Comparison -> b -> b -> OutputConstraint a b CmpLevels :: Comparison -> b -> b -> OutputConstraint a b CmpTeles :: Comparison -> b -> b -> OutputConstraint a b JustSort :: b -> OutputConstraint a b CmpSorts :: Comparison -> b -> b -> OutputConstraint a b Guard :: (OutputConstraint a b) -> ProblemId -> OutputConstraint a b Assign :: b -> a -> OutputConstraint a b TypedAssign :: b -> a -> a -> OutputConstraint a b PostponedCheckArgs :: b -> [a] -> a -> a -> OutputConstraint a b IsEmptyType :: a -> OutputConstraint a b SizeLtSat :: a -> OutputConstraint a b FindInScopeOF :: b -> a -> [(a, a)] -> OutputConstraint a b -- | A subset of OutputConstraint. data OutputConstraint' a b OfType' :: b -> a -> OutputConstraint' a b [ofName] :: OutputConstraint' a b -> b [ofExpr] :: OutputConstraint' a b -> a outputFormId :: OutputForm a b -> b showComparison :: Comparison -> String getConstraints :: TCM [OutputForm Expr Expr] -- | getSolvedInteractionPoints True returns all solutions, even -- if just solved by another, non-interaction meta. -- -- getSolvedInteractionPoints False only returns metas that are -- solved by a non-meta. getSolvedInteractionPoints :: Bool -> TCM [(InteractionId, MetaId, Expr)] typeOfMetaMI :: Rewrite -> MetaId -> TCM (OutputConstraint Expr NamedMeta) typeOfMeta :: Rewrite -> InteractionId -> TCM (OutputConstraint Expr InteractionId) typeOfMeta' :: Rewrite -> (InteractionId, MetaId) -> TCM (OutputConstraint Expr InteractionId) typesOfVisibleMetas :: Rewrite -> TCM [OutputConstraint Expr InteractionId] typesOfHiddenMetas :: Rewrite -> TCM [OutputConstraint Expr NamedMeta] metaHelperType :: Rewrite -> InteractionId -> Range -> String -> TCM (OutputConstraint' Expr Expr) contextOfMeta :: InteractionId -> Rewrite -> TCM [OutputConstraint' Expr Name] -- | Returns the type of the expression in the current environment We wake -- up irrelevant variables just in case the user want to invoke that -- command in an irrelevant context. typeInCurrent :: Rewrite -> Expr -> TCM Expr typeInMeta :: InteractionId -> Rewrite -> Expr -> TCM Expr withInteractionId :: InteractionId -> TCM a -> TCM a withMetaId :: MetaId -> TCM a -> TCM a introTactic :: Bool -> InteractionId -> TCM [String] -- | Runs the given computation as if in an anonymous goal at the end of -- the top-level module. -- -- Sets up current module, scope, and context. atTopLevel :: TCM a -> TCM a -- | Parse a name. parseName :: Range -> String -> TCM QName -- | Returns the contents of the given module. moduleContents :: Rewrite -> Range -> String -> TCM ([Name], [(Name, Type)]) whyInScope :: String -> TCM (Maybe LocalVar, [AbstractName], [AbstractModule]) instance GHC.Base.Functor (Agda.Interaction.BasicOps.OutputForm a) instance GHC.Base.Functor (Agda.Interaction.BasicOps.OutputConstraint a) instance GHC.Read.Read Agda.Interaction.BasicOps.Rewrite instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.TypeChecking.Monad.Base.ProblemConstraint (Agda.TypeChecking.Monad.Base.Closure (Agda.Interaction.BasicOps.OutputForm Agda.Syntax.Abstract.Expr Agda.Syntax.Abstract.Expr)) instance Agda.Syntax.Translation.InternalToAbstract.Reify Agda.TypeChecking.Monad.Base.Constraint (Agda.Interaction.BasicOps.OutputConstraint Agda.Syntax.Abstract.Expr Agda.Syntax.Abstract.Expr) instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Agda.Interaction.BasicOps.OutputForm a b) instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Agda.Interaction.BasicOps.OutputConstraint a b) instance (Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a c, Agda.Syntax.Translation.AbstractToConcrete.ToConcrete b d) => Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (Agda.Interaction.BasicOps.OutputForm a b) (Agda.Interaction.BasicOps.OutputForm c d) instance (Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a c, Agda.Syntax.Translation.AbstractToConcrete.ToConcrete b d) => Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (Agda.Interaction.BasicOps.OutputConstraint a b) (Agda.Interaction.BasicOps.OutputConstraint c d) instance (Agda.Utils.Pretty.Pretty a, Agda.Utils.Pretty.Pretty b) => Agda.Utils.Pretty.Pretty (Agda.Interaction.BasicOps.OutputConstraint' a b) instance (Agda.Syntax.Translation.AbstractToConcrete.ToConcrete a c, Agda.Syntax.Translation.AbstractToConcrete.ToConcrete b d) => Agda.Syntax.Translation.AbstractToConcrete.ToConcrete (Agda.Interaction.BasicOps.OutputConstraint' a b) (Agda.Interaction.BasicOps.OutputConstraint' c d) module Agda.Interaction.CommandLine data ExitCode a Continue :: ExitCode a ContinueIn :: TCEnv -> ExitCode a Return :: a -> ExitCode a type Command a = (String, [String] -> TCM (ExitCode a)) matchCommand :: String -> [Command a] -> Either [String] ([String] -> TCM (ExitCode a)) interaction :: String -> [Command a] -> (String -> TCM (ExitCode a)) -> IM a -- | The interaction loop. interactionLoop :: TCM (Maybe Interface) -> IM () continueAfter :: TCM a -> TCM (ExitCode b) -- | Set envCurrentPath to optInputFile. withCurrentFile :: TCM a -> TCM a loadFile :: TCM () -> [String] -> TCM () showConstraints :: [String] -> TCM () showMetas :: [String] -> TCM () showScope :: TCM () metaParseExpr :: InteractionId -> String -> TCM Expr actOnMeta :: [String] -> (InteractionId -> Expr -> TCM a) -> TCM a giveMeta :: [String] -> TCM () refineMeta :: [String] -> TCM () retryConstraints :: TCM () evalIn :: [String] -> TCM () parseExpr :: String -> TCM Expr evalTerm :: String -> TCM (ExitCode a) typeOf :: [String] -> TCM () typeIn :: [String] -> TCM () showContext :: [String] -> TCM () -- | The logo that prints when Agda is started in interactive mode. splashScreen :: String -- | The help message help :: [Command a] -> IO () module Agda.Interaction.MakeCase type CaseContext = Maybe ExtLamInfo -- | Find the clause whose right hand side is the given meta BY SEARCHING -- THE WHOLE SIGNATURE. Returns the original clause, before record -- patterns have been translated away. Raises an error if there is no -- matching clause. -- -- Andreas, 2010-09-21: This looks like a SUPER UGLY HACK to me. You are -- walking through the WHOLE signature to find an information you have -- thrown away earlier. (shutter with disgust). This code fails for -- record rhs because they have been eta-expanded, so the MVar is gone. findClause :: MetaId -> TCM (CaseContext, QName, Clause) -- | Parse variables (visible or hidden), returning their de Bruijn -- indices. Used in makeCase. parseVariables :: InteractionId -> Range -> [String] -> TCM [Int] -- | Entry point for case splitting tactic. makeCase :: InteractionId -> Range -> String -> TCM (CaseContext, [Clause]) makeAbsurdClause :: QName -> SplitClause -> TCM Clause -- | Make a clause with a question mark as rhs. makeAbstractClause :: QName -> SplitClause -> TCM Clause deBruijnIndex :: Expr -> TCM Nat module Agda.TypeChecking.Serialise.Instances.Internal instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.Signature instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.Section instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Internal.Tele a) instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Utils.Permutation.Permutation instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Utils.Permutation.Drop a) instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Internal.Elim' a) instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Internal.ConHead instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Internal.Type' a) instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Internal.Abs a) instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Internal.Term instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Internal.Level instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Internal.PlusLevel instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Internal.LevelAtom instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Internal.Sort instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.DisplayForm instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.TypeChecking.Monad.Base.Open a) instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.CtxId instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.DisplayTerm instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.MutualId instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.Definition instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.NLPat instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.RewriteRule instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.Projection instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.ExtLamInfo instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.Polarity instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Positivity.Occurrence.Occurrence instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.Defn instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.TypeChecking.CompiledClause.WithArity a) instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.TypeChecking.CompiledClause.Case a) instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.CompiledClause.CompiledClauses instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.TypeChecking.Monad.Base.FunctionInverse' a) instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.TermHead instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Internal.Clause instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Internal.ClauseBodyF a) instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.Syntax.Internal.ConPatternInfo instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.Syntax.Internal.Pattern' a) instance Agda.TypeChecking.Serialise.Base.EmbPrj a => Agda.TypeChecking.Serialise.Base.EmbPrj (Agda.TypeChecking.Monad.Base.Builtin a) module Agda.TypeChecking.Serialise.Instances instance Agda.TypeChecking.Serialise.Base.EmbPrj Agda.TypeChecking.Monad.Base.Interface -- | Structure-sharing serialisation of Agda interface files. module Agda.TypeChecking.Serialise -- | Encodes something. To ensure relocatability file paths in positions -- are replaced with module names. encode :: EmbPrj a => a -> TCM ByteString -- | Encodes something. To ensure relocatability file paths in positions -- are replaced with module names. encodeFile :: FilePath -> Interface -> TCM () encodeInterface :: Interface -> TCM ByteString -- | Decodes something. The result depends on the include path. -- -- Returns Nothing if the input does not start with the right -- magic number or some other decoding error is encountered. decode :: EmbPrj a => ByteString -> TCM (Maybe a) decodeFile :: FilePath -> TCM (Maybe Interface) -- | Decodes something. The result depends on the include path. -- -- Returns Nothing if the file does not start with the right magic -- number or some other decoding error is encountered. decodeInterface :: ByteString -> TCM (Maybe Interface) decodeHashes :: ByteString -> Maybe (Hash, Hash) class Typeable a => EmbPrj a where icode a = do { tickICode a; icod_ a } -- | This module deals with finding imported modules and loading their -- interface files. module Agda.Interaction.Imports -- | Are we loading the interface for the user-loaded file or for an -- import? data MainInterface -- | Interface for main file. MainInterface :: MainInterface -- | Interface for imported file. NotMainInterface :: MainInterface -- | Merge an interface into the current proof state. mergeInterface :: Interface -> TCM () addImportedThings :: Signature -> BuiltinThings PrimFun -> Set String -> PatternSynDefns -> TCM () -- | Scope checks the given module. A proper version of the module name -- (with correct definition sites) is returned. scopeCheckImport :: ModuleName -> TCM (ModuleName, Map ModuleName Scope) data MaybeWarnings NoWarnings :: MaybeWarnings SomeWarnings :: Warnings -> MaybeWarnings hasWarnings :: MaybeWarnings -> Bool -- | If the module has already been visited (without warnings), then its -- interface is returned directly. Otherwise the computation is used to -- find the interface and the computed interface is stored for potential -- later use. alreadyVisited :: TopLevelModuleName -> TCM (Interface, MaybeWarnings) -> TCM (Interface, MaybeWarnings) -- | Type checks the main file of the interaction. This could be the file -- loaded in the interacting editor (emacs), or the file passed on the -- command line. -- -- First, the primitive modules are imported. Then, -- getInterface' is called to do the main work. typeCheckMain :: AbsolutePath -> TCM (Interface, MaybeWarnings) -- | Tries to return the interface associated to the given (imported) -- module. The time stamp of the relevant interface file is also -- returned. Calls itself recursively for the imports of the given -- module. May type check the module. An error is raised if a warning is -- encountered. -- -- Do not use this for the main file, use typeCheckMain instead. getInterface :: ModuleName -> TCM Interface -- | See getInterface. getInterface_ :: TopLevelModuleName -> TCM Interface -- | A more precise variant of getInterface. If warnings are -- encountered then they are returned instead of being turned into -- errors. getInterface' :: TopLevelModuleName -> MainInterface -> TCM (Interface, MaybeWarnings) -- | Print the highlighting information contained in the given interface. highlightFromInterface :: Interface -> AbsolutePath -> TCM () readInterface :: FilePath -> TCM (Maybe Interface) -- | Writes the given interface to the given file. Returns the file's new -- modification time stamp, or Nothing if the write failed. writeInterface :: FilePath -> Interface -> TCM () removePrivates :: ScopeInfo -> ScopeInfo -- | Tries to type check a module and write out its interface. The function -- only writes out an interface file if it does not encounter any -- warnings. -- -- If appropriate this function writes out syntax highlighting -- information. createInterface :: AbsolutePath -> TopLevelModuleName -> TCM (Interface, MaybeWarnings) constructIScope :: Interface -> Interface -- | Builds an interface for the current module, which should already have -- been successfully type checked. buildInterface :: AbsolutePath -> TopLevelInfo -> HighlightingInfo -> Set String -> [OptionsPragma] -> TCM Interface -- | Returns (iSourceHash, iFullHash) getInterfaceFileHashes :: FilePath -> TCM (Maybe (Hash, Hash)) moduleHash :: ModuleName -> TCM Hash -- | True if the first file is newer than the second file. If a file -- doesn't exist it is considered to be infinitely old. isNewerThan :: FilePath -> FilePath -> IO Bool instance GHC.Show.Show Agda.Interaction.Imports.MainInterface instance GHC.Classes.Eq Agda.Interaction.Imports.MainInterface -- | Epic compiler backend. module Agda.Compiler.Epic.Compiler -- | Compile an interface into an executable using Epic compilerMain :: Interface -> TCM () module Agda.Compiler.JS.Compiler compilerMain :: Interface -> TCM () compile :: Interface -> TCM () prefix :: [Char] jsMod :: ModuleName -> GlobalId jsFileName :: GlobalId -> String jsMember :: Name -> MemberId global' :: QName -> TCM (Exp, [MemberId]) global :: QName -> TCM (Exp, [MemberId]) reorder :: [Export] -> [Export] reorder' :: Set [MemberId] -> [Export] -> [Export] isTopLevelValue :: Export -> Bool isEmptyObject :: Export -> Bool insertAfter :: Set [MemberId] -> Export -> [Export] -> [Export] curModule :: TCM Module definition :: (QName, Definition) -> TCM Export defn :: QName -> [MemberId] -> Type -> Maybe JSCode -> Defn -> TCM Exp numPars :: [Clause] -> Nat clause :: Clause -> TCM Case mapping :: [Pattern] -> (Nat, Nat, [Exp]) mapping' :: Pattern -> (Nat, Nat, [Exp]) -> (Nat, Nat, [Exp]) pattern :: Pattern -> TCM Patt tag :: QName -> TCM Tag visitorName :: QName -> TCM MemberId body :: ClauseBody -> TCM Exp term :: Term -> TCM Exp isSingleton :: Type -> TCM (Maybe Exp) args :: Int -> Args -> TCM [Exp] qname :: QName -> TCM Exp literal :: Literal -> Exp dummyLambda :: Int -> Exp -> Exp writeModule :: Module -> TCM () compileDir :: TCM FilePath outFile :: GlobalId -> TCM FilePath outFile_ :: TCM FilePath module Agda.Compiler.MAlonzo.Compiler compilerMain :: Bool -> Interface -> TCM () compile :: Interface -> TCM () imports :: TCM [ImportDecl] definitions :: Definitions -> TCM [Decl] -- | Note that the INFINITY, SHARP and FLAT builtins are translated as -- follows (if a CoinductionKit is given): -- --
--   type Infinity a b = b
--   
--   sharp :: a -> a
--   sharp x = x
--   
--   flat :: a -> a
--   flat x = x
--   
definition :: Maybe CoinductionKit -> Definition -> TCM [Decl] -- | Environment for naming of local variables. Invariant: reverse -- ccCxt ++ ccNameSupply data CCEnv CCEnv :: Maybe QName -> NameSupply -> CCContext -> Maybe CompiledClauses -> CCEnv -- | Agda function we are currently compiling. [ccFunName] :: CCEnv -> Maybe QName -- | Supply of fresh names [ccNameSupply] :: CCEnv -> NameSupply -- | Names currently in scope [ccCxt] :: CCEnv -> CCContext -- | Naive catch-all implementation. If an inner case has no catch-all -- clause, we use the one from its parent. [ccCatchAll] :: CCEnv -> Maybe CompiledClauses type NameSupply = [Name] type CCContext = [Name] mapNameSupply :: (NameSupply -> NameSupply) -> CCEnv -> CCEnv mapContext :: (CCContext -> CCContext) -> CCEnv -> CCEnv -- | Initial environment for expression generation. initCCEnv :: Maybe QName -> CCEnv -- | Term variables are de Bruijn indices. lookupIndex :: Int -> CCContext -> Name -- | Case variables are de Bruijn levels. lookupLevel :: Int -> CCContext -> Name type CC = ReaderT CCEnv TCM -- | Compile a case tree into nested case and record expressions. casetree :: CompiledClauses -> CC Exp -- | Replace the current catch-all clause with a new one, if given. updateCatchAll :: Maybe CompiledClauses -> CC a -> CC a conAlts :: Int -> Map QName (WithArity CompiledClauses) -> CC [Alt] litAlts :: Map Literal CompiledClauses -> CC [Alt] catchAllAlts :: Maybe CompiledClauses -> CC [Alt] branch :: Pat -> CompiledClauses -> CC Alt -- | Replace de Bruijn Level x by n new variables. replaceVar :: Int -> Int -> ([Name] -> CC a) -> CC a -- | Precondition: Map not empty. mkRecord :: Map QName Exp -> CC Exp recConFromProj :: QName -> TCM ConHead -- | Introduce lambdas such that n variables are in scope. lambdasUpTo :: Int -> CC Exp -> CC Exp -- | Introduce n lambdas. lambdas :: Int -> CC Exp -> CC Exp -- | Introduce n variables into the context. intros :: Int -> ([Name] -> CC Exp) -> CC Exp -- | Prefix a Haskell expression with lambda abstractions. mkLams :: [Name] -> Exp -> Exp checkConstructorType :: QName -> TCM [Decl] checkCover :: QName -> HaskellType -> Nat -> [QName] -> TCM [Decl] -- | Move somewhere else! conArityAndPars :: QName -> TCM (Nat, Nat) clause :: QName -> Maybe String -> (Nat, Bool, Clause) -> TCM Decl argpatts :: [NamedArg Pattern] -> [Pat] -> TCM [Pat] clausebody :: ClauseBody -> TCM Exp closedTerm :: Term -> TCM Exp -- | Extract Agda term to Haskell expression. Irrelevant arguments are -- extracted as (). Types are extracted as (). -- DontCare outside of irrelevant arguments is extracted as -- error. term :: Term -> CC Exp -- | Irrelevant arguments are replaced by Haskells' (). term' :: Arg Term -> CC Exp literal :: Literal -> TCM Exp hslit :: Literal -> Literal litqname :: QName -> Exp litqnamepat :: QName -> Pat condecl :: QName -> TCM (Nat, ConDecl) cdecl :: QName -> Nat -> ConDecl tvaldecl :: QName -> Induction -> Nat -> Nat -> [ConDecl] -> Maybe Clause -> [Decl] infodecl :: QName -> Decl hsCast :: Exp -> Exp hsCast' :: Exp -> Exp hsCoerce :: Exp -> Exp writeModule :: Module -> TCM () rteModule :: Module compileDir :: TCM FilePath outFile' :: (Pretty a, TransformBi ModuleName (Wrap a)) => a -> TCM (FilePath, FilePath) outFile :: ModuleName -> TCM FilePath outFile_ :: TCM FilePath callGHC :: Bool -> Interface -> TCM () module Agda.Auto.Auto -- | Entry point for Auto tactic (Agsy). -- --
--   auto ii rng s = return (res, mmsg)
--   
-- -- If mmsg = Just msg, the message msg produced by Agsy -- should be displayed to the user. -- -- The result res of the Auto tactic can be one of the following -- three: -- --
    --
  1. Left [(ii,s)] A list of solutions s for -- interaction ids ii. In particular, Left [] means -- Agsy found no solution.
  2. --
  3. Right (Left cs) A list of clauses (the user allowed -- case-split).
  4. --
  5. Right (Right s) A refinement for the interaction id -- ii in which Auto was invoked.
  6. --
auto :: InteractionId -> Range -> String -> TCM (Either [(InteractionId, String)] (Either [String] String), Maybe String) module Agda.Interaction.InteractionTop -- | Auxiliary state of an interactive computation. data CommandState CommandState :: [InteractionId] -> Maybe (AbsolutePath, ClockTime) -> CommandLineOptions -> OldInteractionScopes -> CommandState -- | The interaction points of the buffer, in the order in which they -- appear in the buffer. The interaction points are recorded in -- theTCState, but when new interaction points are added by give -- or refine Agda does not ensure that the ranges of later interaction -- points are updated. [theInteractionPoints] :: CommandState -> [InteractionId] -- | The file which the state applies to. Only stored if the module was -- successfully type checked (potentially with warnings). The -- ClockTime is the modification time stamp of the file when it -- was last loaded. [theCurrentFile] :: CommandState -> Maybe (AbsolutePath, ClockTime) -- | Reset the options on each reload to these. [optionsOnReload] :: CommandState -> CommandLineOptions -- | We remember (the scope of) old interaction points to make it possible -- to parse and compute highlighting information for the expression that -- it got replaced by. [oldInteractionScopes] :: CommandState -> OldInteractionScopes type OldInteractionScopes = Map InteractionId ScopeInfo -- | Initial auxiliary interaction state initCommandState :: CommandState -- | Monad for computing answers to interactive commands. -- -- CommandM is TCM extended with state CommandState. type CommandM = StateT CommandState TCM -- | Build an opposite action to lift for state monads. revLift :: MonadState st m => (forall c. m c -> st -> k (c, st)) -> (forall b. k b -> m b) -> (forall x. (m a -> k x) -> k x) -> m a -- | Opposite of liftIO for CommandM. Use only if main errors -- are already catched. commandMToIO :: (forall x. (CommandM a -> IO x) -> IO x) -> CommandM a -- | Lift a TCM action transformer to a CommandM action transformer. liftCommandMT :: (forall a. TCM a -> TCM a) -> CommandM a -> CommandM a -- | Put a response by the callback function given by -- stInteractionOutputCallback. putResponse :: Response -> CommandM () -- | A Lens for theInteractionPoints. modifyTheInteractionPoints :: ([InteractionId] -> [InteractionId]) -> CommandM () -- | A Lens for oldInteractionScopes. modifyOldInteractionScopes :: (OldInteractionScopes -> OldInteractionScopes) -> CommandM () insertOldInteractionScope :: InteractionId -> ScopeInfo -> CommandM () removeOldInteractionScope :: InteractionId -> CommandM () getOldInteractionScope :: InteractionId -> CommandM ScopeInfo -- | Run an IOTCM value, catch the exceptions, emit output -- -- If an error happens the state of CommandM does not change, but -- stPersistent may change (which contains successfully loaded interfaces -- for example). runInteraction :: IOTCM -> CommandM () -- | An interactive computation. type Interaction = Interaction' Range data Interaction' range -- | cmd_load m includes loads the module in file m, -- using includes as the include directories. Cmd_load :: FilePath -> [FilePath] -> Interaction' range -- | cmd_compile b m includes compiles the module in file -- m using the backend b, using includes as -- the include directories. Cmd_compile :: Backend -> FilePath -> [FilePath] -> Interaction' range Cmd_constraints :: Interaction' range -- | Show unsolved metas. If there are no unsolved metas but unsolved -- constraints show those instead. Cmd_metas :: Interaction' range -- | Shows all the top-level names in the given module, along with their -- types. Uses the top-level scope. Cmd_show_module_contents_toplevel :: Rewrite -> String -> Interaction' range Cmd_solveAll :: Interaction' range -- | Parse the given expression (as if it were defined at the top-level of -- the current module) and infer its type. Cmd_infer_toplevel :: Rewrite -> String -> Interaction' range -- | Parse and type check the given expression (as if it were defined at -- the top-level of the current module) and normalise it. Cmd_compute_toplevel :: Bool -> String -> Interaction' range -- | cmd_load_highlighting_info source loads syntax highlighting -- information for the module in source, and asks Emacs to apply -- highlighting info from this file. -- -- If the module does not exist, or its module name is malformed or -- cannot be determined, or the module has not already been visited, or -- the cached info is out of date, then no highlighting information is -- printed. -- -- This command is used to load syntax highlighting information when a -- new file is opened, and it would probably be annoying if jumping to -- the definition of an identifier reset the proof state, so this command -- tries not to do that. One result of this is that the command uses the -- current include directories, whatever they happen to be. Cmd_load_highlighting_info :: FilePath -> Interaction' range -- | Tells Agda to compute highlighting information for the expression just -- spliced into an interaction point. Cmd_highlight :: InteractionId -> range -> String -> Interaction' range -- | Tells Agda whether or not to show implicit arguments. ShowImplicitArgs :: Bool -> Interaction' range -- | Toggle display of implicit arguments. ToggleImplicitArgs :: Interaction' range -- | Goal commands -- -- If the range is noRange, then the string comes from the -- minibuffer rather than the goal. Cmd_give :: InteractionId -> range -> String -> Interaction' range Cmd_refine :: InteractionId -> range -> String -> Interaction' range Cmd_intro :: Bool -> InteractionId -> range -> String -> Interaction' range Cmd_refine_or_intro :: Bool -> InteractionId -> range -> String -> Interaction' range Cmd_auto :: InteractionId -> range -> String -> Interaction' range Cmd_context :: Rewrite -> InteractionId -> range -> String -> Interaction' range Cmd_helper_function :: Rewrite -> InteractionId -> range -> String -> Interaction' range Cmd_infer :: Rewrite -> InteractionId -> range -> String -> Interaction' range Cmd_goal_type :: Rewrite -> InteractionId -> range -> String -> Interaction' range -- | Displays the current goal and context. Cmd_goal_type_context :: Rewrite -> InteractionId -> range -> String -> Interaction' range -- | Displays the current goal and context and infers the type of an -- expression. Cmd_goal_type_context_infer :: Rewrite -> InteractionId -> range -> String -> Interaction' range -- | Shows all the top-level names in the given module, along with their -- types. Uses the scope of the given goal. Cmd_show_module_contents :: Rewrite -> InteractionId -> range -> String -> Interaction' range Cmd_make_case :: InteractionId -> range -> String -> Interaction' range Cmd_compute :: Bool -> InteractionId -> range -> String -> Interaction' range Cmd_why_in_scope :: InteractionId -> range -> String -> Interaction' range Cmd_why_in_scope_toplevel :: String -> Interaction' range -- | Displays version of the running Agda Cmd_show_version :: Interaction' range type IOTCM = IOTCM' Range data IOTCM' range IOTCM :: FilePath -> HighlightingLevel -> HighlightingMethod -> (Interaction' range) -> IOTCM' range -- | The Parse monad. StateT state holds the remaining input. type Parse a = ExceptT String (StateT String Identity) a -- | Converter from the type of reads to Parse The first -- paramter is part of the error message in case the parse fails. readsToParse :: String -> (String -> Maybe (a, String)) -> Parse a parseToReadsPrec :: Parse a -> Int -> String -> [(a, String)] -- | Demand an exact string. exact :: String -> Parse () readParse :: Read a => Parse a parens' :: Parse a -> Parse a -- | Can the command run even if the relevant file has not been loaded into -- the state? independent :: Interaction -> Bool -- | Interpret an interaction interpret :: Interaction -> CommandM () -- | Print open metas nicely. showOpenMetas :: TCM [String] -- | cmd_load' file includes unsolvedOk cmd loads the module in -- file file, using includes as the include -- directories. -- -- If type checking completes without any exceptions having been -- encountered then the command cmd r is executed, where -- r is the result of typeCheckMain. cmd_load' :: FilePath -> [FilePath] -> Bool -> ((Interface, MaybeWarnings) -> CommandM ()) -> CommandM () -- | Set envCurrentPath to theCurrentFile, if any. withCurrentFile :: CommandM a -> CommandM a -- | Available backends. data Backend MAlonzo :: Backend MAlonzoNoMain :: Backend Epic :: Backend JS :: Backend data GiveRefine Give :: GiveRefine Refine :: GiveRefine -- | A "give"-like action (give, refine, etc). -- -- give_gen ii rng s give_ref mk_newtxt acts on interaction -- point ii occupying range rng, placing the new -- content given by string s, and replacing ii by the -- newly created interaction points in the state. give_gen :: InteractionId -> Range -> String -> GiveRefine -> CommandM () highlightExpr :: Expr -> TCM () -- | Sorts interaction points based on their ranges. sortInteractionPoints :: [InteractionId] -> TCM [InteractionId] -- | Pretty-prints the type of the meta-variable. prettyTypeOfMeta :: Rewrite -> InteractionId -> TCM Doc -- | Pretty-prints the context of the given meta-variable. prettyContext :: Rewrite -> Bool -> InteractionId -> TCM Doc -- | Create type of application of new helper function that would solve the -- goal. cmd_helper_function :: Rewrite -> InteractionId -> Range -> String -> TCM Doc -- | Displays the current goal, the given document, and the current -- context. cmd_goal_type_context_and :: Doc -> Rewrite -> InteractionId -> Range -> String -> StateT CommandState (TCMT IO) () -- | Shows all the top-level names in the given module, along with their -- types. showModuleContents :: Rewrite -> Range -> String -> CommandM () -- | Explain why something is in scope. whyInScope :: String -> CommandM () -- | Sets the command line options and updates the status information. setCommandLineOptions' :: CommandLineOptions -> CommandM () -- | Computes some status information. status :: CommandM Status -- | Displays/updates status information. displayStatus :: CommandM () -- | display_info does what display_info' False -- does, but additionally displays some status information (see -- status and displayStatus). display_info :: DisplayInfo -> CommandM () refreshStr :: [String] -> String -> ([String], String) nameModifiers :: [String] -- | Kill meta numbers and ranges from all metas (? and -- _). lowerMeta :: (ExprLike a) => a -> a -- | Parses and scope checks an expression (using the "inside scope" as the -- scope), performs the given command with the expression as input, and -- displays the result. parseAndDoAtToplevel :: (Expr -> TCM Expr) -> (Doc -> DisplayInfo) -> String -> CommandM () -- | Tell to highlight the code using the given highlighting info (unless -- it is Nothing). tellToUpdateHighlighting :: Maybe (HighlightingInfo, ModuleToSource) -> IO [Response] -- | Tells the Emacs mode to go to the first error position (if any). tellEmacsToJumpToError :: Range -> [Response] instance GHC.Show.Show Agda.Interaction.InteractionTop.GiveRefine instance GHC.Classes.Eq Agda.Interaction.InteractionTop.GiveRefine instance Data.Traversable.Traversable Agda.Interaction.InteractionTop.IOTCM' instance Data.Foldable.Foldable Agda.Interaction.InteractionTop.IOTCM' instance GHC.Base.Functor Agda.Interaction.InteractionTop.IOTCM' instance GHC.Read.Read range => GHC.Read.Read (Agda.Interaction.InteractionTop.IOTCM' range) instance Data.Traversable.Traversable Agda.Interaction.InteractionTop.Interaction' instance Data.Foldable.Foldable Agda.Interaction.InteractionTop.Interaction' instance GHC.Base.Functor Agda.Interaction.InteractionTop.Interaction' instance GHC.Read.Read range => GHC.Read.Read (Agda.Interaction.InteractionTop.Interaction' range) instance GHC.Read.Read Agda.Interaction.InteractionTop.Backend instance GHC.Show.Show Agda.Interaction.InteractionTop.Backend instance GHC.Read.Read Agda.Syntax.Common.InteractionId instance GHC.Read.Read a => GHC.Read.Read (Agda.Syntax.Position.Range' a) instance GHC.Read.Read a => GHC.Read.Read (Agda.Syntax.Position.Interval' a) instance GHC.Read.Read Agda.Utils.FileName.AbsolutePath instance GHC.Read.Read a => GHC.Read.Read (Agda.Syntax.Position.Position' a) module Agda.Interaction.EmacsTop -- | mimicGHCi is a fake ghci interpreter for the Emacs frontend and -- for interaction tests. -- -- mimicGHCi reads the Emacs frontend commands from stdin, -- interprets them and print the result into stdout. mimicGHCi :: TCM () -- | Agda main module. module Agda.Main -- | The main function runAgda :: TCM () -- | Run Agda with parsed command line options and with a custom HTML -- generator runAgdaWithOptions :: TCM () -> String -> CommandLineOptions -> TCM () -- | Print usage information. printUsage :: IO () -- | Print version information. printVersion :: IO () -- | What to do for bad options. optionError :: String -> IO () -- | Run a TCM action in IO; catch and pretty print errors. runTCMPrettyErrors :: TCM () -> IO () -- | Main main :: IO ()