cryptol-2.13.0: Cryptol: The Language of Cryptography
Copyright(c) 2015-2016 Galois Inc.
LicenseBSD3
Maintainercryptol@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cryptol.Utils.Ident

Description

 
Synopsis

Module names

data ModPath Source #

Idnetifies a possibly nested module

Instances

Instances details
Eq ModPath Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

(==) :: ModPath -> ModPath -> Bool #

(/=) :: ModPath -> ModPath -> Bool #

Ord ModPath Source # 
Instance details

Defined in Cryptol.Utils.Ident

Show ModPath Source # 
Instance details

Defined in Cryptol.Utils.Ident

Generic ModPath Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep ModPath :: Type -> Type #

Methods

from :: ModPath -> Rep ModPath x #

to :: Rep ModPath x -> ModPath #

NFData ModPath Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: ModPath -> () #

PP ModPath Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

ppPrec :: Int -> ModPath -> Doc Source #

type Rep ModPath Source # 
Instance details

Defined in Cryptol.Utils.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.

data ModName Source #

Top-level Module names are just text.

Instances

Instances details
Eq ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

(==) :: ModName -> ModName -> Bool #

(/=) :: ModName -> ModName -> Bool #

Ord ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Show ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Generic ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep ModName :: Type -> Type #

Methods

from :: ModName -> Rep ModName x #

to :: Rep ModName x -> ModName #

NFData ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: ModName -> () #

PPName ModName Source # 
Instance details

Defined in Cryptol.Utils.PP

PP ModName Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

ppPrec :: Int -> ModName -> Doc Source #

TVars Module Source # 
Instance details

Defined in Cryptol.TypeCheck.Subst

Methods

apSubst :: Subst -> Module -> 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.

Instance details

Defined in Cryptol.ModuleSystem.NamingEnv

type Rep ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep ModName = D1 ('MetaData "ModName" "Cryptol.Utils.Ident" "cryptol-2.13.0-BA7OuzmYZ3M9j8JsJfXs6b" 'False) (C1 ('MetaCons "ModName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

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.

Identifiers

data Ident Source #

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

Instances details
Eq Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

(==) :: Ident -> Ident -> Bool #

(/=) :: Ident -> Ident -> Bool #

Ord Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

compare :: Ident -> Ident -> Ordering #

(<) :: Ident -> Ident -> Bool #

(<=) :: Ident -> Ident -> Bool #

(>) :: Ident -> Ident -> Bool #

(>=) :: Ident -> Ident -> Bool #

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Show Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

IsString Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

fromString :: String -> Ident #

Generic Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep Ident :: Type -> Type #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

NFData Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: Ident -> () #

PP Ident Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

ppPrec :: Int -> Ident -> Doc Source #

ShowParseable Ident Source # 
Instance details

Defined in Cryptol.TypeCheck.Parseable

type Rep Ident Source # 
Instance details

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)))

Namespaces

data Namespace Source #

Namespaces for names

Constructors

NSValue 
NSType 
NSModule 

Instances

Instances details
Bounded Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Enum Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Eq Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Ord Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Show Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Generic Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep Namespace :: Type -> Type #

NFData Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: Namespace -> () #

PP Namespace Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

ppPrec :: Int -> Namespace -> Doc Source #

type Rep Namespace Source # 
Instance details

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)))

Original names

data OrigName Source #

Identifies an entitiy

Constructors

OrigName 

Instances

Instances details
Eq OrigName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Ord OrigName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Show OrigName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Generic OrigName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep OrigName :: Type -> Type #

Methods

from :: OrigName -> Rep OrigName x #

to :: Rep OrigName x -> OrigName #

NFData OrigName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: OrigName -> () #

PP OrigName Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

ppPrec :: Int -> OrigName -> Doc Source #

type Rep OrigName Source # 
Instance details

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

data PrimIdent Source #

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

Constructors

PrimIdent ModName Text 

Instances

Instances details
Eq PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.Ident

Ord PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.Ident

Show PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.Ident

Generic PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep PrimIdent :: Type -> Type #

NFData PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: PrimIdent -> () #

type Rep PrimIdent Source # 
Instance details

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)))

prelPrim :: Text -> PrimIdent Source #

A shortcut to make (non-infix) primitives in the prelude.