Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Fortran.Repr.Value.Scalar.Common
Description
Common definitions for Fortran scalar representations.
Synopsis
- data SomeFKinded k1 (ft :: k -> Type) where
- SomeFKinded :: forall {k} (ft :: k -> Type) (fk :: k). (SingKind k, SingI fk, Data (ft fk)) => ft fk -> SomeFKinded k ft
- someFKindedKind :: forall {k1} k2 (ft :: k1 -> Type). SomeFKinded k2 ft -> Demote k2
- class FKinded a where
Documentation
data SomeFKinded k1 (ft :: k -> Type) where Source #
Convenience wrapper which multiple Fortran tag-kinded intrinsic types fit.
A type ft
takes some type fk
of kind k
, and we are permitted to move the
type between the term and type levels using the included singleton instances.
For example, integers are kinded with type level FTInt
s. So we can define an
integer with an existential ("unknown") kind with the type
. By pattern matching on it, we recover the hidden kind tag (as well as
obtaining the value).SomeFKinded
FTInt
FInt
Note that many type classes usually derived generically (e.g.
Binary
) instances should be manually derived on this wrapper type.
TODO give a better explanation why?
Constructors
SomeFKinded :: forall {k} (ft :: k -> Type) (fk :: k). (SingKind k, SingI fk, Data (ft fk)) => ft fk -> SomeFKinded k ft |
Instances
(forall (fk :: k2). Show (ft fk)) => Out (SomeFKinded k1 ft) Source # | |
Defined in Language.Fortran.Repr.Value.Scalar.Common Methods docPrec :: Int -> SomeFKinded k1 ft -> Doc # doc :: SomeFKinded k1 ft -> Doc # docList :: [SomeFKinded k1 ft] -> Doc # | |
(SingKind k, forall (fk :: k). SingI fk, forall (fk :: k). Data (ft fk), Typeable ft, Typeable k) => Data (SomeFKinded k ft) Source # | |
Defined in Language.Fortran.Repr.Value.Scalar.Common Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SomeFKinded k ft -> c (SomeFKinded k ft) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SomeFKinded k ft) # toConstr :: SomeFKinded k ft -> Constr # dataTypeOf :: SomeFKinded k ft -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SomeFKinded k ft)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SomeFKinded k ft)) # gmapT :: (forall b. Data b => b -> b) -> SomeFKinded k ft -> SomeFKinded k ft # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SomeFKinded k ft -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SomeFKinded k ft -> r # gmapQ :: (forall d. Data d => d -> u) -> SomeFKinded k ft -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SomeFKinded k ft -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SomeFKinded k ft -> m (SomeFKinded k ft) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SomeFKinded k ft -> m (SomeFKinded k ft) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SomeFKinded k ft -> m (SomeFKinded k ft) # | |
(forall (fk :: k1). Show (ft fk)) => Show (SomeFKinded k2 ft) Source # | GHC can derive stock |
Defined in Language.Fortran.Repr.Value.Scalar.Common Methods showsPrec :: Int -> SomeFKinded k2 ft -> ShowS # show :: SomeFKinded k2 ft -> String # showList :: [SomeFKinded k2 ft] -> ShowS # | |
(Binary (Demote k), SingKind k, forall (fk :: k). SingI fk => Binary (ft fk), forall (fk :: k). Data (ft fk)) => Binary (SomeFKinded k ft) Source # | For any Fortran type WARNING: This instance is only sound for types where each kind tag value is used once at most (meaning if you know the fkind, you know the constructor). Note that the |
Defined in Language.Fortran.Repr.Value.Scalar.Common Methods put :: SomeFKinded k ft -> Put # get :: Get (SomeFKinded k ft) # putList :: [SomeFKinded k ft] -> Put # |
someFKindedKind :: forall {k1} k2 (ft :: k1 -> Type). SomeFKinded k2 ft -> Demote k2 Source #
Recover some TYPE(x)
's kind (the x
).
class FKinded a where Source #
A kinded Fortran value.
Associated Types
The Haskell type used to record this Fortran type's kind.
For every Fortran kind of this Fortran type a
, the underlying
representation b
has the given constraints.
Instances
FKinded FComplex Source # | |||||||||
Defined in Language.Fortran.Repr.Value.Scalar.Complex Associated Types
| |||||||||
FKinded FInt Source # | |||||||||
FKinded FReal Source # | |||||||||
Defined in Language.Fortran.Repr.Value.Scalar.Real Associated Types
|