| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Language.Fortran.Common.Array
Synopsis
- data Dim a = Dim {}
- data Dims (t :: Type -> Type) a- = DimsExplicitShape (t (Dim a))
- | DimsAssumedSize (Maybe (t (Dim a))) a
- | DimsAssumedShape (t a)
 
- prettyIntersperse :: Foldable t => Doc -> t Doc -> Doc
- prettyAfter :: Foldable t => Doc -> t Doc -> Doc
- dimsTraverse :: forall (t :: Type -> Type) f a. (Traversable t, Applicative f) => Dims t (f a) -> f (Dims t a)
- dimsLength :: forall (t :: Type -> Type) a. Foldable t => Dims t a -> Int
Documentation
A single array dimension with bounds of type a.
- Numa =>- Dima
- Dim(- Expression- ())
- Numa =>- Dim(- Maybea)
Instances
| Foldable Dim Source # | |||||
| Defined in Language.Fortran.Common.Array Methods fold :: Monoid m => Dim m -> m # foldMap :: Monoid m => (a -> m) -> Dim a -> m # foldMap' :: Monoid m => (a -> m) -> Dim a -> m # foldr :: (a -> b -> b) -> b -> Dim a -> b # foldr' :: (a -> b -> b) -> b -> Dim a -> b # foldl :: (b -> a -> b) -> b -> Dim a -> b # foldl' :: (b -> a -> b) -> b -> Dim a -> b # foldr1 :: (a -> a -> a) -> Dim a -> a # foldl1 :: (a -> a -> a) -> Dim a -> a # elem :: Eq a => a -> Dim a -> Bool # maximum :: Ord a => Dim a -> a # | |||||
| Traversable Dim Source # | |||||
| Functor Dim Source # | |||||
| Out a => Out (Dim a) Source # | Fortran syntax uses  | ||||
| Data a => Data (Dim a) Source # | |||||
| Defined in Language.Fortran.Common.Array Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dim a -> c (Dim a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dim a) # dataTypeOf :: Dim a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Dim a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dim a)) # gmapT :: (forall b. Data b => b -> b) -> Dim a -> Dim a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dim a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dim a -> r # gmapQ :: (forall d. Data d => d -> u) -> Dim a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dim a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dim a -> m (Dim a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dim a -> m (Dim a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dim a -> m (Dim a) # | |||||
| Generic (Dim a) Source # | |||||
| Defined in Language.Fortran.Common.Array Associated Types 
 | |||||
| Show a => Show (Dim a) Source # | |||||
| Binary a => Binary (Dim a) Source # | |||||
| NFData a => NFData (Dim a) Source # | |||||
| Defined in Language.Fortran.Common.Array | |||||
| Out (Dim a) => Pretty (Dim a) Source # | |||||
| Defined in Language.Fortran.Common.Array | |||||
| Eq a => Eq (Dim a) Source # | |||||
| Ord a => Ord (Dim a) Source # | |||||
| type Rep (Dim a) Source # | |||||
| Defined in Language.Fortran.Common.Array type Rep (Dim a) = D1 ('MetaData "Dim" "Language.Fortran.Common.Array" "fortran-src-0.16.7-GLmWuRZOFJo2g1dq61LjMD" 'False) (C1 ('MetaCons "Dim" 'PrefixI 'True) (S1 ('MetaSel ('Just "dimLower") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "dimUpper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) | |||||
data Dims (t :: Type -> Type) a Source #
Fortran array dimensions, defined by a list of Dims storing lower and
   upper bounds.
You select the list type t (which should be Functor, Foldable and
 Traversable) and the bound type a (e.g. Int).
Using a non-empty list type such as NonEmpty will
 disallow representing zero-dimension arrays, providing extra soundness.
Note the following excerpt from the F2018 standard (8.5.8.2 Explicit-shape array):
If the upper bound is less than the lower bound, the range is empty, the extent in that dimension is zero, and the array is of zero size.
Note that the Foldable instance does not provide "dimension-like" access to
 this type. That is, length (a :: Dims t a)a represents. Use dimsLength for that.
Constructors
| DimsExplicitShape | Explicit-shape array. All dimensions are known. | 
| Fields 
 | |
| DimsAssumedSize | Assumed-size array. The final dimension has no upper bound (it is obtained from its effective argument). Earlier dimensions may be defined like explicit-shape arrays. | 
| DimsAssumedShape | Assumed-shape array. Shape is taken from effective argument. We store the lower bound for each dimension, and thus also the rank (via list length). | 
| Fields 
 | |
Instances
| Foldable t => Foldable (Dims t) Source # | |||||
| Defined in Language.Fortran.Common.Array Methods fold :: Monoid m => Dims t m -> m # foldMap :: Monoid m => (a -> m) -> Dims t a -> m # foldMap' :: Monoid m => (a -> m) -> Dims t a -> m # foldr :: (a -> b -> b) -> b -> Dims t a -> b # foldr' :: (a -> b -> b) -> b -> Dims t a -> b # foldl :: (b -> a -> b) -> b -> Dims t a -> b # foldl' :: (b -> a -> b) -> b -> Dims t a -> b # foldr1 :: (a -> a -> a) -> Dims t a -> a # foldl1 :: (a -> a -> a) -> Dims t a -> a # elem :: Eq a => a -> Dims t a -> Bool # maximum :: Ord a => Dims t a -> a # minimum :: Ord a => Dims t a -> a # | |||||
| Traversable t => Traversable (Dims t) Source # | |||||
| Functor t => Functor (Dims t) Source # | |||||
| (Foldable t, Functor t, Out (Dim a), Out a) => Out (Dims t a) Source # | |||||
| (Data a, Data (t a), Data (t (Dim a)), Typeable t) => Data (Dims t a) Source # | |||||
| Defined in Language.Fortran.Common.Array Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dims t a -> c (Dims t a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dims t a) # toConstr :: Dims t a -> Constr # dataTypeOf :: Dims t a -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Dims t a)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Dims t a)) # gmapT :: (forall b. Data b => b -> b) -> Dims t a -> Dims t a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dims t a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dims t a -> r # gmapQ :: (forall d. Data d => d -> u) -> Dims t a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dims t a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dims t a -> m (Dims t a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dims t a -> m (Dims t a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dims t a -> m (Dims t a) # | |||||
| Generic (Dims t a) Source # | |||||
| Defined in Language.Fortran.Common.Array Associated Types 
 | |||||
| (Show a, Show (t a), Show (t (Dim a))) => Show (Dims t a) Source # | |||||
| (Binary a, Binary (t a), Binary (t (Dim a))) => Binary (Dims t a) Source # | |||||
| (NFData a, NFData (t a), NFData (t (Dim a))) => NFData (Dims t a) Source # | |||||
| Defined in Language.Fortran.Common.Array | |||||
| Out (Dims t a) => Pretty (Dims t a) Source # | |||||
| Defined in Language.Fortran.Common.Array | |||||
| (Eq a, Eq (t a), Eq (t (Dim a))) => Eq (Dims t a) Source # | |||||
| (Ord a, Ord (t a), Ord (t (Dim a))) => Ord (Dims t a) Source # | This instance is purely for convenience. No definition of ordering is provided, and the implementation may change at any time. | ||||
| Defined in Language.Fortran.Common.Array | |||||
| type Rep (Dims t a) Source # | |||||
| Defined in Language.Fortran.Common.Array type Rep (Dims t a) = D1 ('MetaData "Dims" "Language.Fortran.Common.Array" "fortran-src-0.16.7-GLmWuRZOFJo2g1dq61LjMD" 'False) (C1 ('MetaCons "DimsExplicitShape" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (t (Dim a)))) :+: (C1 ('MetaCons "DimsAssumedSize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (t (Dim a)))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "DimsAssumedShape" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (t a))))) | |||||
dimsTraverse :: forall (t :: Type -> Type) f a. (Traversable t, Applicative f) => Dims t (f a) -> f (Dims t a) Source #