cryptol-2.9.0: Cryptol: The Language of Cryptography

Copyright(c) 2015-2016 Galois Inc.
LicenseBSD3
Maintainercryptol@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Cryptol.Utils.Ident

Contents

Description

 
Synopsis

Module names

data ModName Source #

Module names are just text.

Instances
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 -> () #

PP ModName Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

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

type Rep ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep ModName = D1 (MetaData "ModName" "Cryptol.Utils.Ident" "cryptol-2.9.0-4aSi1YZNBynFQwh9aOpllR" 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
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

Identifiers for primitived

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

prelPrim :: Text -> PrimIdent Source #

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