Safe Haskell | None |
---|---|
Language | Haskell2010 |
Embeds Fortran's type system in Haskell via the D
GADT.
Note: Phantom Types and GADTs
Lots of the data types in this module are parameterised by phantom types. These are types which appear at the type-level, but not at the value level. They are there to make things more type-safe.
In addition, a lot of the data types are GADTs. In a phantom-type-indexed GADT, the phantom type often restricts which GADT constructors a particular value may be an instance of. This is very useful for restricting value-level terms based on type-level information.
Synopsis
- data D a where
- newtype Bool8 = Bool8 {}
- newtype Bool16 = Bool16 {}
- newtype Bool32 = Bool32 {}
- newtype Bool64 = Bool64 {}
- newtype Char8 = Char8 {}
- newtype PrimS a = PrimS {
- getPrimS :: a
- data Prim p k a where
- PInt8 :: Prim 'P8 'BTInt Int8
- PInt16 :: Prim 'P16 'BTInt Int16
- PInt32 :: Prim 'P32 'BTInt Int32
- PInt64 :: Prim 'P64 'BTInt Int64
- PBool8 :: Prim 'P8 'BTLogical Bool8
- PBool16 :: Prim 'P16 'BTLogical Bool16
- PBool32 :: Prim 'P32 'BTLogical Bool32
- PBool64 :: Prim 'P64 'BTLogical Bool64
- PFloat :: Prim 'P32 'BTReal Float
- PDouble :: Prim 'P64 'BTReal Double
- PChar :: Prim 'P8 'BTChar Char8
- data Index a where
- data ArrValue a where
- newtype Array i a = Array [a]
- data Field f field where
- data Record name fields where
- dIndex :: Index i -> D i
- dArrValue :: ArrValue a -> D a
- overField :: (f a -> g b) -> Field f '(name, a) -> Field g '(name, b)
- overField' :: (forall a. f a -> g a) -> Field f nv -> Field g nv
- traverseField' :: Functor t => (forall a. f a -> t (g a)) -> Field f nv -> t (Field g nv)
- zipFieldsWith :: (forall a. f a -> g a -> h a) -> Field f nv -> Field g nv -> Field h nv
- zip3FieldsWith :: (forall a. f a -> g a -> h a -> i a) -> Field f nv -> Field g nv -> Field h nv -> Field i nv
Fortran Types
This is the main embedding of Fortran types. A value of type D a
represents
the Fortran type which corresponds to the Haskell type a
. a
is a phantom
type parameter. There is at most one instance of D a
for each a
. This means
that a value of type D a
acts as a kind of proof that it possible to have a
Fortran type corresponding to the Haskell type a
-- and that when you match on
D a
knowing the particular a
you have, you know which constructor you will
get. This is a nice property because it means that GHC (with
-fwarn-incomplete-patterns
) will not warn when you match on an impossible
case. It eliminates situations where you'd otherwise write error "impossible:
..."
.
is for primitive types. It contains a valueDPrim
p :: D (PrimS
a)p
of type
for somePrim
p k ap
,k
,a
. When matching on something of typeD (
, you know it can only contain a primitive type.PrimS
a)
is for arrays. It contains instances ofDArray
i v :: D (Array
i v)
andIndex
i
.ArrValue
a
is a proof thatIndex
ii
can be used as an index, and
is a proof thatArrValue
aa
can be stored in arrays.
is for user-defined data types. The type has a name, represented at the type level by the type parameterDData
s xs :: D (Record
name fs)name
of kindSymbol
. The constructor containss ::
, which acts as a sort of value-level representation of the name.SSymbol
nameSSymbol
is from thesingletons
library. It also containsxs ::
.Rec
(Field
D) fsfs
is a type-level list of pairs, pairing field names with field types.
is a value-level pair ofField
D '(fname, b)
andSSymbol
fnameD b
. The vinyl record is a list of fields, one for each pair infs
.
Semantic Types
This newtype wrapper is used in DPrim
for semantic primitive types. This means
that when matching on something of type
, we know it can't be
an array or a record.D
(PrimS
a)
Instances
Eq a => Eq (PrimS a) Source # | |
Show a => Show (PrimS a) Source # | |
LiftD (PrimS Double) AlgReal Source # | |
LiftD (PrimS Float) AlgReal Source # | |
LiftD (PrimS Int8) Integer Source # | |
LiftD (PrimS Int16) Integer Source # | |
LiftD (PrimS Int32) Integer Source # | |
LiftD (PrimS Int64) Integer Source # | |
LiftD (PrimS Char8) Word8 Source # | |
LiftD (PrimS Bool64) Bool Source # | |
LiftD (PrimS Bool32) Bool Source # | |
LiftD (PrimS Bool16) Bool Source # | |
LiftD (PrimS Bool8) Bool Source # | |
Primitive Types
data Prim p k a where Source #
Lists the allowed primitive Fortran types. For example,
represents 8-bit integers. PInt8
:: Prim
'P8
'BTInt
Int8
Prim
has three phantom type
parameters: precision, base type and semantic Haskell type. Precision is the
number of bits used to store values of that type. The base type represents the
corresponding Fortran base type, e.g. integer
or real
. Constructors are only
provided for those Fortran types which are semantically valid, so for example no
constructor is provided for a 16-bit real. A value of type
can be
seen as a proof that there is some Fortran primitive type with those parameters.Prim
p k a
PInt8 :: Prim 'P8 'BTInt Int8 | |
PInt16 :: Prim 'P16 'BTInt Int16 | |
PInt32 :: Prim 'P32 'BTInt Int32 | |
PInt64 :: Prim 'P64 'BTInt Int64 | |
PBool8 :: Prim 'P8 'BTLogical Bool8 | |
PBool16 :: Prim 'P16 'BTLogical Bool16 | |
PBool32 :: Prim 'P32 'BTLogical Bool32 | |
PBool64 :: Prim 'P64 'BTLogical Bool64 | |
PFloat :: Prim 'P32 'BTReal Float | |
PDouble :: Prim 'P64 'BTReal Double | |
PChar :: Prim 'P8 'BTChar Char8 |
Arrays
Specifies which types can be used as array indices.
data ArrValue a where Source #
Specifies which types can be stored in arrays. Currently arrays of arrays are not supported.
An array with a phantom index type. Mostly used at the type-level to
constrain instances of
etc.D
(Array i a)
Array [a] |
Records
data Record name fields where Source #
A type of records with the given name
and fields
. Mostly used at the
type level to constrain instances of
etc.D
(Record name fields)
Combinators
dArrValue :: ArrValue a -> D a Source #
Anything that can be stored in Fortran arrays is a valid Fortran type.
overField :: (f a -> g b) -> Field f '(name, a) -> Field g '(name, b) Source #
Given a field with known contents, we can change the functor and value type.
overField' :: (forall a. f a -> g a) -> Field f nv -> Field g nv Source #
Given a field with unknown contents, we can change the functor but not the value type.