Skip to content

Commit

Permalink
finally adding those exotic but cool formats i've talked about forever
Browse files Browse the repository at this point in the history
  • Loading branch information
cartazio committed Feb 20, 2024
1 parent 7d3dc5e commit b98b1ba
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 2 deletions.
1 change: 1 addition & 0 deletions numerical.cabal
Expand Up @@ -65,6 +65,7 @@ library
Numerical.Array.Layout.Base
Numerical.Array.Layout.Dense
Numerical.Array.Layout.Sparse
Numerical.Array.Layout.Het
--Numerical.Array.Layout.Dense.Builder
Numerical.Array.Layout.Builder
Numerical.Array
Expand Down
7 changes: 5 additions & 2 deletions src/Numerical/Array/Layout/Base.hs
Expand Up @@ -11,7 +11,7 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}

{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE CPP #-}

Expand All @@ -20,7 +20,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}


{-# LANGUAGE NoImplicitPrelude #-}

module Numerical.Array.Layout.Base(
Layout(..)
Expand Down Expand Up @@ -51,6 +51,7 @@ module Numerical.Array.Layout.Base(
) where


import Data.Dynamic
import Data.Data
import Data.Kind(Type)
import Numerical.Nat
Expand Down Expand Up @@ -280,6 +281,8 @@ class Layout form (rank :: Nat) | form -> rank where
form -> address -> Int -> Maybe address




{-# MINIMAL basicToAddress, basicToIndex, basicNextAddress,basicNextIndex
,basicAddressRange,basicLogicalShape,basicCompareIndex
, transposedLayout, basicAddressPopCount,basicLogicalForm, basicAffineAddressShift #-}
Expand Down
22 changes: 22 additions & 0 deletions src/Numerical/Array/Layout/Het.hs
@@ -0,0 +1,22 @@

{-# LANGUAGE TypeOperators #-}

module Numerical.Array.Layout.Het where

import Numerical.Array.Layout.Base
import Data.Dynamic


--- this operation is needed
--- so that we can define composite formats, eg
--- zero copy concatenations of arrays with mixed but
--- compatible formats
fromSomeAddress :: (Typeable addr, addr ~ LayoutAddress form ) => p form -> Dynamic -> Maybe addr

Check failure on line 14 in src/Numerical/Array/Layout/Het.hs

View workflow job for this annotation

GitHub Actions / GHC8.6.5,cabal3.2.0.0,ubuntu-latest

• Illegal equational constraint addr ~ LayoutAddress form

Check failure on line 14 in src/Numerical/Array/Layout/Het.hs

View workflow job for this annotation

GitHub Actions / GHC8.8.3,cabal3.2.0.0,ubuntu-latest

• Illegal equational constraint addr ~ LayoutAddress form

Check failure on line 14 in src/Numerical/Array/Layout/Het.hs

View workflow job for this annotation

GitHub Actions / GHC8.10.3,cabal3.2.0.0,ubuntu-latest

• Illegal equational constraint addr ~ LayoutAddress form

Check failure on line 14 in src/Numerical/Array/Layout/Het.hs

View workflow job for this annotation

GitHub Actions / GHClatest,cabal3.2.0.0,ubuntu-latest

• Illegal equational constraint addr ~ LayoutAddress form

Check failure on line 14 in src/Numerical/Array/Layout/Het.hs

View workflow job for this annotation

GitHub Actions / GHClatest,caballatest,macOS-latest

• Illegal equational constraint addr ~ LayoutAddress form

Check failure on line 14 in src/Numerical/Array/Layout/Het.hs

View workflow job for this annotation

GitHub Actions / GHClatest,caballatest,ubuntu-latest

• Illegal equational constraint addr ~ LayoutAddress form
fromSomeAddress _ x = fromDynamic x
{-
The purpose of this module is to illustrate
and substantiate zero copy vertical and horizontal
concatenation of compatibly oriented Rectilinear formats
-}

newtype SomeAddr = MkAddr Dynamic

0 comments on commit b98b1ba

Please sign in to comment.