global-0.2.0.1: Library enabling unique top-level declarations

Safe HaskellNone
LanguageHaskell2010

Data.Global

Synopsis

Documentation

class UniqueDeclaration u where Source

Types that can be uniquely declared on the top level.

Like Monad, this type class itself is not "magical". Its instances, however, may be primitive, at least conceptually, much like IOs Monad instance.

Individual instances may be accompanied with certain caveats. Each individual instance should include in its documentation what these are. These caveats may affect surrounding code, perhaps in ways detrimental to the program's performance or efficiency; users should thus consider isolating "global" declarations in their own .Global module; this is not necessarily necessary for every instance. See the documentation of the particular instance to see how the declarations should be declared.

The type should be monomorphic, or concrete enough, to be type safe, so that the references cannot be treated as multiple concreet types (writing [Integer] to a reference that has the type IORef [a] and subsequently reading [Char] can cause the program to core dump). Ensuring this safety is the responsibility of the implementer of the instances of this type class; other users of this library who do not extend this class's functionality generally do not need to be concerned whether the program will run correctly at run-time, since the mistakes, which can violate type safety, will be caught at compile-time and the code will not build (this is, however, not intrinsically guaranteed, much like the monad laws: they are expected to be followed). It is worth reiterating that instances of this class need to be sure to not allow code with such erroneous types to compile. For more information about type safety, see the documentation of unsafePerformIO.

Example:

un "lives" =:: ([| 3 |], ut [t| Integer |] :: UT TVar)

lives would then refer to the TVar and would initially contain the value 3.

Methods

(=::) Source

Arguments

:: UN u

Name of reference

-> (UV, UT u)

Initial value, accompanied with the internal type and tagged with the unique constructor so that the correct instance can be unambiguously determined.

An initial value may not make sense in some contexts; implementations of instances may choose to ignore this value, as well as the internal type and unique constructor. Implementations should document how this parameter is used.

-> Q [Dec]

Top-level declarations for the unique declaration.

At least a definition for the name and a type signature should be provided.

Declare uniquely.

Instances

UniqueDeclaration MVar

Declaring unique MVars; see also TMVar; caveats are the same as those of IORefs.

The initial value is used so that the reference refers initially to that value.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration MSem

Declaring unique MSems.

The initial value; which is, in this case, determines the initial quantity of the semaphore; is passed to newMSem; the types thus must match. The internal type is given to the MSem constructor to construct a semaphore based on an integral type.

NB: When multiple units of a resource are needed simultaneously, consider using MSemNs to avoid deadlocks.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration MSemN

Declaring unique MSemNs.

The initial value; which is, in this case, determines the initial quantity of the semaphore; is passed to newMSemN; the types thus must match. The internal type is given to the MSemN constructor to construct a semaphore based on an integral type.

NB: When multiple units of a resource are needed simultaneously, consider using MSemNs to avoid deadlocks.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration MSampleVar

Declaring unique MSampleVars; caveats are the same as those of IORefs.

The initial value is used so that the reference refers initially to that value.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration TVar

Declaring unique TVars; caveats are the same as those of IORefs.

The initial value is used so that the reference refers initially to that value.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration IORef

Declaring unique IORefs; for thread-safe handling of mutable data, see TVar.

The initial value is used so that the reference refers initially to that value.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same preconditions apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration TMVar

Declaring unique TMVars; caveats are the same as those of IORefs.

The initial value is used so that the reference refers initially to that value.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (Const RWLock)

Declaring unique RWLocks.

The initial value and the internal type are ignored.

NB: When multiple units of a resource are needed simultaneously, consider using QSemNs to avoid deadlocks.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (Const QSemN)

Declaring unique QSemNs.

The initial value; which is, in this case, determines the initial quantity of the semaphore; is passed to newQSemN; the types thus must match. The internal type is ignored.

NB: When multiple units of a resource are needed simultaneously, consider using QSemNs to avoid deadlocks.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (Const QSem)

Declaring unique QSems.

The initial value; which is, in this case, determines the initial quantity of the semaphore; is passed to newQSem; the types thus must match. The internal type is ignored.

NB: When multiple units of a resource are needed simultaneously, consider using QSemNs to avoid deadlocks.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (UDEmpty MVar)

Declaring unique MVars that are initially empty; see also TMVar.

The initial value is ignored.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (UDEmpty MSampleVar)

Declaring unique MSampleVarss that are initially empty; caveats are the same as those of MVars that are initially empty.

The initial value is ignored.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (UDEmpty Chan)

Declaring unique Chans that are initially empty; for thread-safe atomic accessing of channels, see TChan; caveats are the same as those of MVars that are initially empty.

The initial value is ignored.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (UDEmpty TMVar)

Declaring unique TMVars that are initially empty; caveats are the same as those of MVars that are initially empty.

The initial value is ignored.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (UDEmpty TChan)

Declaring unique TChans that are initially empty; caveats are the same as those of MVars that are initially empty.

The initial value is ignored.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

newtype UDEmpty u a Source

Identity type wrapper that indicates that the unique declaration should be "empty" by default.

Constructors

UDEmpty (u a) 

Instances

UniqueDeclaration (UDEmpty MVar)

Declaring unique MVars that are initially empty; see also TMVar.

The initial value is ignored.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (UDEmpty MSampleVar)

Declaring unique MSampleVarss that are initially empty; caveats are the same as those of MVars that are initially empty.

The initial value is ignored.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (UDEmpty Chan)

Declaring unique Chans that are initially empty; for thread-safe atomic accessing of channels, see TChan; caveats are the same as those of MVars that are initially empty.

The initial value is ignored.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (UDEmpty TMVar)

Declaring unique TMVars that are initially empty; caveats are the same as those of MVars that are initially empty.

The initial value is ignored.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

UniqueDeclaration (UDEmpty TChan)

Declaring unique TChans that are initially empty; caveats are the same as those of MVars that are initially empty.

The initial value is ignored.

These preconditions apply to GHC 7.0.4 and base-0.4.3.1 and likely similar versions and implementations as well.

In its low-level implementation, this instance uses unsafePerformIO; thus, the same caveats apply to this instance, particularly those regarding top-level declarations (referential transparency cannot be violated here). As of base-4.3.1.0, these conditions, that the user needs to be aware of, are the following: * Compile the declarations with the compiler flag -fno-cse. This prevents multiple references from being substituted to refer to the same data. This flag thus does not affect the semantics of the program, but may potentially adversely affect its performance; thus, isolating in a .Global module may be advisable in some cases. This condition is not strictly necessary when only one declaration is made in a module, since the compiler cannot substitute multiple references to refer to same data.

If your code behaves differently when optimizations are enabled, ensure that this flag is indeed being used when the declarations are being compiled. Setting or passing this flag is NOT handled automatically by this implementation; it is the responsibility of users of this implementation to ensure that such appropriate behaviour is set when necessary.

This can be accomplished by placing the line {--} in the file in which the declarations are declared, before the "module" line.

type UN u = Tagged (Cnt u) Name Source

Tagged name type.

un :: UniqueDeclaration u => String -> UN u Source

Construct a name for a unique declaration from a string.

type UT c = Tagged (Cnt c) TypeQ Source

Tagged unique declaration type.

ut :: UniqueDeclaration c => TypeQ -> UT c Source

Tagged unique declaration type constructor.

type Cnt c = c () Source

Transform a container with kind * -> * into a concrete type * by applying the type '()' to the constructor.

Intended to be used for tagging types for unique declarations.

type UV = ExpQ Source

An expression for a value contained in a unique declaration.

monomorphic :: Type -> Bool Source

Determine whether a type is polymorphic.

type QSemQuantity = Int Source

The type of values that supply an initial quantity for quantity semaphores.

translateExtsToTH' :: Exp -> Exp Source

Translate an Exts AST to a Template Haskell AST, failing when the translation result is not a Template Haskell AST.

This is defined in terms of translateExtsToTH

utl :: Exp -> UV Source

Apply translateExtsToTH' and lift the result into the Q monad.

This is often used with ud to refer to variables whose names are not required to be in scope when the quotation is expanded, in a very roundabout way.

"utl" can be thought of as a mnemonic for "unique", "translate" and "lift"; and will be updated appropriately to reflect changes to UV.

For example, to enable self-referential recursion by referring to variables whose names are not yet in scope, an expression quotation [| … |] can usually be written as utl [ud| … |].

ud :: QuasiQuoter Source

Alias to the QuasiQuoter hs, which does not require names to be in scope when the quotation is expanded, which enables self-referential recursion.

uninitialized :: Q Exp Source

An alternative to providing an initial value.

Warning: attempting to read uninitialized references can cause the program to crash.