Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Fortran.Model.Singletons
Description
Data kinds and corresponding singletons (via the singletons
library) for kinds
used in various places in Language.Fortran.Model.
As documentation in Template Haskell is not yet supported, documentation for each data type is given here.
Precision
The precision, in bits, of an intrinsic Fortran data type.
BasicType
The basic type of an intrinsic Fortran data type.
OpKind
TODO
precMax
Finds the maximum of two precisions. Use PrecMax
at the type level and sPrecMax
for singletons.
basicTypeMax
Finds the 'largest' (with respect to the size of the set it semantically
represents) of numeric basic types. Also works with non-numeric basic types, but
the result in that case is unspecified. Use BasicTypeMax
at the type level and
sBasicTypeMax
for singletons.
Documentation
Instances
Instances
Constructors
OKLit | |
OKNum | |
OKEq | |
OKRel | |
OKLogical | |
OKLookup | |
OKDeref | |
OKWriteArr | |
OKWriteData |
Instances
Eq OpKind Source # | |
Ord OpKind Source # | |
Show OpKind Source # | |
SingKind OpKind Source # | |
SingI 'OKLit Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKNum Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKEq Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKRel Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKLogical Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKLookup Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKDeref Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKWriteArr Source # | |
Defined in Language.Fortran.Model.Singletons Methods sing :: Sing 'OKWriteArr | |
SingI 'OKWriteData Source # | |
Defined in Language.Fortran.Model.Singletons Methods sing :: Sing 'OKWriteData | |
type Demote OpKind Source # | |
Defined in Language.Fortran.Model.Singletons | |
type Sing Source # | |
Defined in Language.Fortran.Model.Singletons type Sing = SOpKind |
type BTRealSym0 = BTReal :: BasicType Source #
type BTLogicalSym0 = BTLogical :: BasicType Source #
type BTCharSym0 = BTChar :: BasicType Source #
type OKLogicalSym0 = OKLogical :: OpKind Source #
type OKLookupSym0 = OKLookup :: OpKind Source #
type OKDerefSym0 = OKDeref :: OpKind Source #
type OKWriteArrSym0 = OKWriteArr :: OpKind Source #
type OKWriteDataSym0 = OKWriteData :: OpKind Source #
type family BasicTypeMax a a where ... Source #
Equations
BasicTypeMax a_6989586621679392761 a_6989586621679392763 = Apply (Apply MaxSym0 a_6989586621679392761) a_6989586621679392763 |
type BasicTypeMaxSym2 (a6989586621679392768 :: BasicType) (a6989586621679392769 :: BasicType) = BasicTypeMax a6989586621679392768 a6989586621679392769 :: BasicType Source #
data BasicTypeMaxSym1 a6989586621679392768 a6989586621679392769 where Source #
Constructors
BasicTypeMaxSym1KindInference :: SameKind (Apply (BasicTypeMaxSym1 a6989586621679392768) arg) (BasicTypeMaxSym2 a6989586621679392768 arg) => BasicTypeMaxSym1 a6989586621679392768 a6989586621679392769 |
Instances
SingI d => SingI (BasicTypeMaxSym1 d :: TyFun BasicType BasicType -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons Methods sing :: Sing (BasicTypeMaxSym1 d) | |
SuppressUnusedWarnings (BasicTypeMaxSym1 a6989586621679392768 :: TyFun BasicType BasicType -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons Methods suppressUnusedWarnings :: () | |
type Apply (BasicTypeMaxSym1 a6989586621679392768 :: TyFun BasicType BasicType -> Type) (a6989586621679392769 :: BasicType) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply (BasicTypeMaxSym1 a6989586621679392768 :: TyFun BasicType BasicType -> Type) (a6989586621679392769 :: BasicType) = BasicTypeMaxSym2 a6989586621679392768 a6989586621679392769 |
data BasicTypeMaxSym0 a6989586621679392768 where Source #
Constructors
BasicTypeMaxSym0KindInference :: SameKind (Apply BasicTypeMaxSym0 arg) (BasicTypeMaxSym1 arg) => BasicTypeMaxSym0 a6989586621679392768 |
Instances
SingI BasicTypeMaxSym0 Source # | |
Defined in Language.Fortran.Model.Singletons Methods sing :: Sing BasicTypeMaxSym0 | |
SuppressUnusedWarnings BasicTypeMaxSym0 Source # | |
Defined in Language.Fortran.Model.Singletons Methods suppressUnusedWarnings :: () | |
type Apply BasicTypeMaxSym0 (a6989586621679392768 :: BasicType) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply BasicTypeMaxSym0 (a6989586621679392768 :: BasicType) = BasicTypeMaxSym1 a6989586621679392768 |
type family PrecMax a a where ... Source #
Equations
PrecMax a_6989586621679392772 a_6989586621679392774 = Apply (Apply MaxSym0 a_6989586621679392772) a_6989586621679392774 |
type PrecMaxSym2 (a6989586621679392779 :: Precision) (a6989586621679392780 :: Precision) = PrecMax a6989586621679392779 a6989586621679392780 :: Precision Source #
data PrecMaxSym1 a6989586621679392779 a6989586621679392780 where Source #
Constructors
PrecMaxSym1KindInference :: SameKind (Apply (PrecMaxSym1 a6989586621679392779) arg) (PrecMaxSym2 a6989586621679392779 arg) => PrecMaxSym1 a6989586621679392779 a6989586621679392780 |
Instances
SingI d => SingI (PrecMaxSym1 d :: TyFun Precision Precision -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons Methods sing :: Sing (PrecMaxSym1 d) | |
SuppressUnusedWarnings (PrecMaxSym1 a6989586621679392779 :: TyFun Precision Precision -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons Methods suppressUnusedWarnings :: () | |
type Apply (PrecMaxSym1 a6989586621679392779 :: TyFun Precision Precision -> Type) (a6989586621679392780 :: Precision) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply (PrecMaxSym1 a6989586621679392779 :: TyFun Precision Precision -> Type) (a6989586621679392780 :: Precision) = PrecMaxSym2 a6989586621679392779 a6989586621679392780 |
data PrecMaxSym0 a6989586621679392779 where Source #
Constructors
PrecMaxSym0KindInference :: SameKind (Apply PrecMaxSym0 arg) (PrecMaxSym1 arg) => PrecMaxSym0 a6989586621679392779 |
Instances
SingI PrecMaxSym0 Source # | |
Defined in Language.Fortran.Model.Singletons Methods sing :: Sing PrecMaxSym0 | |
SuppressUnusedWarnings PrecMaxSym0 Source # | |
Defined in Language.Fortran.Model.Singletons Methods suppressUnusedWarnings :: () | |
type Apply PrecMaxSym0 (a6989586621679392779 :: Precision) Source # | |
Defined in Language.Fortran.Model.Singletons |
type family Compare_6989586621679394002 a a where ... Source #
Equations
type Compare_6989586621679394002Sym2 (a6989586621679394007 :: Precision) (a6989586621679394008 :: Precision) = Compare_6989586621679394002 a6989586621679394007 a6989586621679394008 :: Ordering Source #
data Compare_6989586621679394002Sym1 a6989586621679394007 a6989586621679394008 where Source #
Constructors
Compare_6989586621679394002Sym1KindInference :: SameKind (Apply (Compare_6989586621679394002Sym1 a6989586621679394007) arg) (Compare_6989586621679394002Sym2 a6989586621679394007 arg) => Compare_6989586621679394002Sym1 a6989586621679394007 a6989586621679394008 |
Instances
SuppressUnusedWarnings (Compare_6989586621679394002Sym1 a6989586621679394007 :: TyFun Precision Ordering -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons Methods suppressUnusedWarnings :: () | |
type Apply (Compare_6989586621679394002Sym1 a6989586621679394007 :: TyFun Precision Ordering -> Type) (a6989586621679394008 :: Precision) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply (Compare_6989586621679394002Sym1 a6989586621679394007 :: TyFun Precision Ordering -> Type) (a6989586621679394008 :: Precision) = Compare_6989586621679394002Sym2 a6989586621679394007 a6989586621679394008 |
data Compare_6989586621679394002Sym0 a6989586621679394007 where Source #
Constructors
Compare_6989586621679394002Sym0KindInference :: SameKind (Apply Compare_6989586621679394002Sym0 arg) (Compare_6989586621679394002Sym1 arg) => Compare_6989586621679394002Sym0 a6989586621679394007 |
Instances
SuppressUnusedWarnings Compare_6989586621679394002Sym0 Source # | |
Defined in Language.Fortran.Model.Singletons Methods suppressUnusedWarnings :: () | |
type Apply Compare_6989586621679394002Sym0 (a6989586621679394007 :: Precision) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply Compare_6989586621679394002Sym0 (a6989586621679394007 :: Precision) = Compare_6989586621679394002Sym1 a6989586621679394007 |
type family Compare_6989586621679394011 a a where ... Source #
Equations
type Compare_6989586621679394011Sym2 (a6989586621679394016 :: BasicType) (a6989586621679394017 :: BasicType) = Compare_6989586621679394011 a6989586621679394016 a6989586621679394017 :: Ordering Source #
data Compare_6989586621679394011Sym1 a6989586621679394016 a6989586621679394017 where Source #
Constructors
Compare_6989586621679394011Sym1KindInference :: SameKind (Apply (Compare_6989586621679394011Sym1 a6989586621679394016) arg) (Compare_6989586621679394011Sym2 a6989586621679394016 arg) => Compare_6989586621679394011Sym1 a6989586621679394016 a6989586621679394017 |
Instances
SuppressUnusedWarnings (Compare_6989586621679394011Sym1 a6989586621679394016 :: TyFun BasicType Ordering -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons Methods suppressUnusedWarnings :: () | |
type Apply (Compare_6989586621679394011Sym1 a6989586621679394016 :: TyFun BasicType Ordering -> Type) (a6989586621679394017 :: BasicType) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply (Compare_6989586621679394011Sym1 a6989586621679394016 :: TyFun BasicType Ordering -> Type) (a6989586621679394017 :: BasicType) = Compare_6989586621679394011Sym2 a6989586621679394016 a6989586621679394017 |
data Compare_6989586621679394011Sym0 a6989586621679394016 where Source #
Constructors
Compare_6989586621679394011Sym0KindInference :: SameKind (Apply Compare_6989586621679394011Sym0 arg) (Compare_6989586621679394011Sym1 arg) => Compare_6989586621679394011Sym0 a6989586621679394016 |
Instances
SuppressUnusedWarnings Compare_6989586621679394011Sym0 Source # | |
Defined in Language.Fortran.Model.Singletons Methods suppressUnusedWarnings :: () | |
type Apply Compare_6989586621679394011Sym0 (a6989586621679394016 :: BasicType) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply Compare_6989586621679394011Sym0 (a6989586621679394016 :: BasicType) = Compare_6989586621679394011Sym1 a6989586621679394016 |
type family Equals_6989586621679394018 a b where ... Source #
Equations
Equals_6989586621679394018 P8 P8 = TrueSym0 | |
Equals_6989586621679394018 P16 P16 = TrueSym0 | |
Equals_6989586621679394018 P32 P32 = TrueSym0 | |
Equals_6989586621679394018 P64 P64 = TrueSym0 | |
Equals_6989586621679394018 P128 P128 = TrueSym0 | |
Equals_6989586621679394018 (_ :: Precision) (_ :: Precision) = FalseSym0 |
type family Equals_6989586621679394022 a b where ... Source #
Equations
Equals_6989586621679394022 BTInt BTInt = TrueSym0 | |
Equals_6989586621679394022 BTReal BTReal = TrueSym0 | |
Equals_6989586621679394022 BTLogical BTLogical = TrueSym0 | |
Equals_6989586621679394022 BTChar BTChar = TrueSym0 | |
Equals_6989586621679394022 (_ :: BasicType) (_ :: BasicType) = FalseSym0 |
data SPrecision :: Precision -> Type where Source #
Constructors
SP8 :: SPrecision (P8 :: Precision) | |
SP16 :: SPrecision (P16 :: Precision) | |
SP32 :: SPrecision (P32 :: Precision) | |
SP64 :: SPrecision (P64 :: Precision) | |
SP128 :: SPrecision (P128 :: Precision) |
Instances
TestCoercion SPrecision Source # | |
Defined in Language.Fortran.Model.Singletons Methods testCoercion :: forall (a :: k) (b :: k). SPrecision a -> SPrecision b -> Maybe (Coercion a b) # | |
TestEquality SPrecision Source # | |
Defined in Language.Fortran.Model.Singletons Methods testEquality :: forall (a :: k) (b :: k). SPrecision a -> SPrecision b -> Maybe (a :~: b) # |
data SBasicType :: BasicType -> Type where Source #
Constructors
SBTInt :: SBasicType (BTInt :: BasicType) | |
SBTReal :: SBasicType (BTReal :: BasicType) | |
SBTLogical :: SBasicType (BTLogical :: BasicType) | |
SBTChar :: SBasicType (BTChar :: BasicType) |
Instances
TestCoercion SBasicType Source # | |
Defined in Language.Fortran.Model.Singletons Methods testCoercion :: forall (a :: k) (b :: k). SBasicType a -> SBasicType b -> Maybe (Coercion a b) # | |
TestEquality SBasicType Source # | |
Defined in Language.Fortran.Model.Singletons Methods testEquality :: forall (a :: k) (b :: k). SBasicType a -> SBasicType b -> Maybe (a :~: b) # |
data SOpKind :: OpKind -> Type where Source #
Constructors
SOKLit :: SOpKind (OKLit :: OpKind) | |
SOKNum :: SOpKind (OKNum :: OpKind) | |
SOKEq :: SOpKind (OKEq :: OpKind) | |
SOKRel :: SOpKind (OKRel :: OpKind) | |
SOKLogical :: SOpKind (OKLogical :: OpKind) | |
SOKLookup :: SOpKind (OKLookup :: OpKind) | |
SOKDeref :: SOpKind (OKDeref :: OpKind) | |
SOKWriteArr :: SOpKind (OKWriteArr :: OpKind) | |
SOKWriteData :: SOpKind (OKWriteData :: OpKind) |
sPrecMax :: forall (t :: Precision) (t :: Precision). Sing t -> Sing t -> Sing (Apply (Apply PrecMaxSym0 t) t :: Precision) Source #
sBasicTypeMax :: forall (t :: BasicType) (t :: BasicType). Sing t -> Sing t -> Sing (Apply (Apply BasicTypeMaxSym0 t) t :: BasicType) Source #