Copyright | (c) 2015-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data ModPath
- apPathRoot :: (ModName -> ModName) -> ModPath -> ModPath
- modPathCommon :: ModPath -> ModPath -> Maybe (ModPath, [Ident], [Ident])
- topModuleFor :: ModPath -> ModName
- modPathSplit :: ModPath -> (ModName, [Ident])
- data ModName
- modNameToText :: ModName -> Text
- textToModName :: Text -> ModName
- modNameChunks :: ModName -> [String]
- packModName :: [Text] -> ModName
- preludeName :: ModName
- preludeReferenceName :: ModName
- floatName :: ModName
- suiteBName :: ModName
- arrayName :: ModName
- primeECName :: ModName
- interactiveName :: ModName
- noModuleName :: ModName
- exprModName :: ModName
- isParamInstModName :: ModName -> Bool
- paramInstModName :: ModName -> ModName
- notParamInstModName :: ModName -> ModName
- data Ident
- packIdent :: String -> Ident
- packInfix :: String -> Ident
- unpackIdent :: Ident -> String
- mkIdent :: Text -> Ident
- mkInfix :: Text -> Ident
- isInfixIdent :: Ident -> Bool
- nullIdent :: Ident -> Bool
- identText :: Ident -> Text
- modParamIdent :: Ident -> Ident
- data Namespace
- allNamespaces :: [Namespace]
- data OrigName = OrigName {}
- data PrimIdent = PrimIdent ModName Text
- prelPrim :: Text -> PrimIdent
- floatPrim :: Text -> PrimIdent
- arrayPrim :: Text -> PrimIdent
- suiteBPrim :: Text -> PrimIdent
- primeECPrim :: Text -> PrimIdent
Module names
Idnetifies a possibly nested module
Instances
Eq ModPath Source # | |
Ord ModPath Source # | |
Show ModPath Source # | |
Generic ModPath Source # | |
NFData ModPath Source # | |
Defined in Cryptol.Utils.Ident | |
PP ModPath Source # | |
type Rep ModPath Source # | |
Defined in Cryptol.Utils.Ident type Rep ModPath = D1 ('MetaData "ModPath" "Cryptol.Utils.Ident" "cryptol-2.13.0-BA7OuzmYZ3M9j8JsJfXs6b" 'False) (C1 ('MetaCons "TopModule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModName)) :+: C1 ('MetaCons "Nested" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModPath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) |
modPathCommon :: ModPath -> ModPath -> Maybe (ModPath, [Ident], [Ident]) Source #
Compute a common prefix between two module paths, if any. This is basically "anti-unification" of the two paths, where we compute the longest common prefix, and the remaining differences for each module.
topModuleFor :: ModPath -> ModName Source #
Top-level Module names are just text.
Instances
Eq ModName Source # | |
Ord ModName Source # | |
Show ModName Source # | |
Generic ModName Source # | |
NFData ModName Source # | |
Defined in Cryptol.Utils.Ident | |
PPName ModName Source # | |
Defined in Cryptol.Utils.PP | |
PP ModName Source # | |
TVars Module Source # | |
BindsNames (Module PName) Source # | The naming environment for a single module. This is the mapping from unqualified names to fully qualified names with uniques. |
Defined in Cryptol.ModuleSystem.NamingEnv | |
type Rep ModName Source # | |
Defined in Cryptol.Utils.Ident |
modNameToText :: ModName -> Text Source #
textToModName :: Text -> ModName Source #
modNameChunks :: ModName -> [String] Source #
packModName :: [Text] -> ModName Source #
suiteBName :: ModName Source #
isParamInstModName :: ModName -> Bool Source #
paramInstModName :: ModName -> ModName Source #
Convert a parameterized module's name to the name of the module containing the same definitions but with explicit parameters on each definition.
notParamInstModName :: ModName -> ModName Source #
Identifiers
Identifiers, along with a flag that indicates whether or not they're infix operators. The boolean is present just as cached information from the lexer, and never used during comparisons.
Instances
Eq Ident Source # | |
Ord Ident Source # | |
Show Ident Source # | |
IsString Ident Source # | |
Defined in Cryptol.Utils.Ident fromString :: String -> Ident # | |
Generic Ident Source # | |
NFData Ident Source # | |
Defined in Cryptol.Utils.Ident | |
PP Ident Source # | |
ShowParseable Ident Source # | |
Defined in Cryptol.TypeCheck.Parseable | |
type Rep Ident Source # | |
Defined in Cryptol.Utils.Ident type Rep Ident = D1 ('MetaData "Ident" "Cryptol.Utils.Ident" "cryptol-2.13.0-BA7OuzmYZ3M9j8JsJfXs6b" 'False) (C1 ('MetaCons "Ident" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
unpackIdent :: Ident -> String Source #
isInfixIdent :: Ident -> Bool Source #
modParamIdent :: Ident -> Ident Source #
Namespaces
Namespaces for names
Instances
Bounded Namespace Source # | |
Enum Namespace Source # | |
Defined in Cryptol.Utils.Ident succ :: Namespace -> Namespace # pred :: Namespace -> Namespace # fromEnum :: Namespace -> Int # enumFrom :: Namespace -> [Namespace] # enumFromThen :: Namespace -> Namespace -> [Namespace] # enumFromTo :: Namespace -> Namespace -> [Namespace] # enumFromThenTo :: Namespace -> Namespace -> Namespace -> [Namespace] # | |
Eq Namespace Source # | |
Ord Namespace Source # | |
Defined in Cryptol.Utils.Ident | |
Show Namespace Source # | |
Generic Namespace Source # | |
NFData Namespace Source # | |
Defined in Cryptol.Utils.Ident | |
PP Namespace Source # | |
type Rep Namespace Source # | |
Defined in Cryptol.Utils.Ident type Rep Namespace = D1 ('MetaData "Namespace" "Cryptol.Utils.Ident" "cryptol-2.13.0-BA7OuzmYZ3M9j8JsJfXs6b" 'False) (C1 ('MetaCons "NSValue" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NSType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NSModule" 'PrefixI 'False) (U1 :: Type -> Type))) |
allNamespaces :: [Namespace] Source #
Original names
Identifies an entitiy
Instances
Eq OrigName Source # | |
Ord OrigName Source # | |
Defined in Cryptol.Utils.Ident | |
Show OrigName Source # | |
Generic OrigName Source # | |
NFData OrigName Source # | |
Defined in Cryptol.Utils.Ident | |
PP OrigName Source # | |
type Rep OrigName Source # | |
Defined in Cryptol.Utils.Ident type Rep OrigName = D1 ('MetaData "OrigName" "Cryptol.Utils.Ident" "cryptol-2.13.0-BA7OuzmYZ3M9j8JsJfXs6b" 'False) (C1 ('MetaCons "OrigName" 'PrefixI 'True) (S1 ('MetaSel ('Just "ogNamespace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Namespace) :*: (S1 ('MetaSel ('Just "ogModule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModPath) :*: S1 ('MetaSel ('Just "ogName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)))) |
Identifiers for primitives
A way to identify primitives: we used to use just Ident
, but this
isn't good anymore as now we have primitives in multiple modules.
This is used as a key when we need to lookup details about a specific
primitive. Also, this is intended to mostly be used internally, so
we don't store the fixity flag of the Ident
Instances
Eq PrimIdent Source # | |
Ord PrimIdent Source # | |
Defined in Cryptol.Utils.Ident | |
Show PrimIdent Source # | |
Generic PrimIdent Source # | |
NFData PrimIdent Source # | |
Defined in Cryptol.Utils.Ident | |
type Rep PrimIdent Source # | |
Defined in Cryptol.Utils.Ident type Rep PrimIdent = D1 ('MetaData "PrimIdent" "Cryptol.Utils.Ident" "cryptol-2.13.0-BA7OuzmYZ3M9j8JsJfXs6b" 'False) (C1 ('MetaCons "PrimIdent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
suiteBPrim :: Text -> PrimIdent Source #
primeECPrim :: Text -> PrimIdent Source #