Defining a Torus class - haskell

I would like to define a Torus class representing 2D arrays that wrap around at borders. For example, accessing the array with an index beyond the size of the corresponding dimension should return the element at position i mod arraysize. My class should thus only need to define a get method as such:
class Torus a where
get :: a -> Int -> Int -> b
This definition is imprecise. a is supposed to be a 2D array and b should be the type contained in the array. How can I express this?
Thanks,

I suppose you were only looking for the types in the class:
class Torus t where
get :: t a -> Int -> Int -> a
Or did you look for an appropriate instance?

You can also use functional dependencies or type families in case you want to have something more sophisticated than simple t :: * -> * type:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
class Torus t v | t -> v where
get :: t -> Int -> Int -> v
instance Torus (Vector a) a where
get = ...
or
{-# LANGUAGE TypeFamilies #-}
class Torus t where
type Element t
get :: t -> Int -> Int -> Element t
instance Torus (Vector a) where
type Element (Vector a) = a
get = ...
This requires some GHC extensions though.

Related

Is it possible to promote a value to type level?

Doing this just for fun but I don't end up figuring this out.
Say I have a typeclass that unifies coordinate system on squares and hexagons:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
import Data.Proxy
data Shape = Square | Hexagon
class CoordSystem (k :: Shape) where
type Coord k
-- all coordinates arranged in a 2D list
-- given a side length of the shape
allCoords :: forall p. p k -> Int -> [[Coord k]]
-- neighborhoods of a coordinate.
neighborsOf :: forall p. p k -> Int -> Coord k -> [Coord k]
-- omitting implementations
instance CoordSystem 'Square
instance CoordSystem 'Hexagon
Now suppose I want to use this interface with a s :: Shape that is only known at runtime. But to make use of this interface, at some point I'll need a function like this:
-- none of those two works:
-- promote :: CoordSystem k => Shape -> Proxy (k :: Shape) -- signature 1
-- promote :: Shape -> forall k. CoordSystem k => Proxy (k :: Shape)
promote s = case s of
Square -> Proxy #'Square
Hexagon -> Proxy #'Hexagon
However this does not work, if signature 1 is uncommented:
• Couldn't match type ‘k’ with ‘'Square’
‘k’ is a rigid type variable bound by
the type signature for:
promote :: forall (k :: Shape). CoordSystem k => Shape -> Proxy k
at SO.hs:28:1-55
Expected type: Proxy k
Actual type: Proxy 'Square
Understandably, none of 'Square, 'Hexagon, k :: Shape unifies with others, so I have no idea whether this is possible.
I also feel type erasure shouldn't be an issue here as alternatives of Shape can use to uniquely identify the instance - for such reason I feel singletons could be of use but I'm not familiar with that package to produce any working example either.
The usual way is to use either an existential type or its Church encoding. The encoded version is actually easier to understand at first, I think, and closer to what you already attempted. The problem with your forall k. CoordSystem k => {- ... thing mentioning k -} is that it promises to polymorph into whatever k the user likes (so long as the user likes CoordSystems!). To fix it, you can demand that the user polymorph into whatever k you like.
-- `a` must not mention `k`, since `k` is not
-- in scope in the final return type
promote :: forall a. Shape -> (forall k. CoordSystem k => Tagged k a) -> a
promote Square a = unTagged (a #Square)
promote Hexagon a = unTagged (a #Hexagon)
-- usage example
test = promote Hexagon (unproxy $ \p -> length (allCoords p 15))
Note that on the right hand side of the = sign, a has the type forall k. CoordSystem k => {- ... -} that says the user gets to choose k, but this time you're the user.
Another common option is to use an existential:
data SomeSystem where
-- Proxy to be able to name the wrapped type when matching on a SomeSystem;
-- in some future version of GHC we may be able to name it via pattern-matching
-- on a type application instead, which would be better
SomeSystem :: CoordSystem k => Proxy k -> SomeSystem
Then you would write something like
promote :: Shape -> SomeSystem
promote Square = SomeSystem (Proxy #Square)
promote Hexagon = SomeSystem (Proxy #Hexagon)
-- usage example
test = case promote Hexagon of SomeSystem p -> length (allCoords p 15)
and then the user would pattern match to extract the CoordSystem instance from it.
A final choice is singletons:
data ShapeS k where
SquareS :: ShapeS Square
HexagonS :: ShapeS Hexagon
Here we have made a direct connection between SquareS at the computation level and Square at the type level (resp. HexagonS and Hexagon). Then you can write:
-- N.B. not a rank-2 type, and in particular `a` is
-- now allowed to mention `k`
promote :: ShapeS k -> (CoordSystem k => a) -> a
promote SquareS a = a
promote HexagonS a = a
The singletons package offers tools for automatically deriving the singleton types that correspond to your ADTs.

DataKind Unions

I'm not sure if it is the right terminology, but is it possible to declare function types that take in an 'union' of datakinds?
For example, I know I can do the following:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
...
data Shape'
= Circle'
| Square'
| Triangle'
data Shape :: Shape' -> * where
Circle :: { radius :: Int} -> Shape Circle'
Square :: { side :: Int} -> Shape Square'
Triangle
:: { a :: Int
, b :: Int
, c :: Int}
-> Shape Triangle'
test1 :: Shape Circle' -> Int
test1 = undefined
However, what if I want to take in a shape that is either a circle or a square? What if I also want to take in all shapes for a separate function?
Is there a way for me to either define a set of Shape' kinds to use, or a way for me to allow multiple datakind definitions per data?
Edit:
The usage of unions doesn't seem to work:
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
...
type family Union (a :: [k]) (r :: k) :: Constraint where
Union (x ': xs) x = ()
Union (x ': xs) y = Union xs y
data Shape'
= Circle'
| Square'
| Triangle'
data Shape :: Shape' -> * where
Circle :: { radius :: Int} -> Shape Circle'
Square :: { side :: Int} -> Shape Square'
Triangle
:: { a :: Int
, b :: Int
, c :: Int}
-> Shape Triangle'
test1 :: Union [Circle', Triangle'] s => Shape s -> Int
test1 Circle {} = undefined
test1 Triangle {} = undefined
test1 Square {} = undefined
The part above compiles
You can accomplish something like this in (I think) a reasonably clean way using a type family together with ConstraintKinds and PolyKinds:
type family Union (a :: [k]) (r :: k) :: Constraint where
Union (x ': xs) x = ()
Union (x ': xs) y = Union xs y
test1 :: Union [Circle', Triangle'] s => Shape s -> Int
test1 = undefined
The () above is the empty constraint (it's like an empty "list" of type class constraints).
The first "equation" of the type family makes use of the nonlinear pattern matching available in type families (it uses x twice on the left hand side). The type family also makes use of the fact that if none of the cases match, it will not give you a valid constraint.
You should also be able to use a type-level Boolean instead of ConstraintKinds. That would be a bit more cumbersome and I think it would be best to avoid using a type-level Boolean here (if you can).
Side-note (I can never remember this and I had to look it up for this answer): You get Constraint in-scope by importing it from GHC.Exts.
Edit: Partially disallowing unreachable definitions
Here is a modification to get it to (partially) disallow unreachable definitions as well as invalid calls. It is slightly more roundabout, but it seems to work.
Modify Union to give a * instead of a constraint, like this:
type family Union (a :: [k]) (r :: k) :: * where
Union (x ': xs) x = ()
Union (x ': xs) y = Union xs y
It doesn't matter too much what the type is, as long as it has an inhabitant you can pattern match on, so I give back the () type (the unit type).
This is how you would use it:
test1 :: Shape s -> Union [Circle', Triangle'] s -> Int
test1 Circle {} () = undefined
test1 Triangle {} () = undefined
-- test1 Square {} () = undefined -- This line won't compile
If you forget to match on it (like, if you put a variable name like x instead of matching on the () constructor), it is possible that an unreachable case can be defined. It will still give a type error at the call-site when you actually try to reach that case, though (so, even if you don't match on the Union argument, the call test1 (Square undefined) () will not type check).
Note that it seems the Union argument must come after the Shape argument in order for this to work (fully as described, anyway).
This is getting kind of awful, but I guess you could require a proof that it's either a circle or a square using Data.Type.Equality:
test1 :: Either (s :~: Circle') (s :~: Square') -> Shape s -> Int
Now the user has to give an extra argument (a "proof term") saying which one it is.
In fact you can use the proof term idea to "complete" bradm's solution, with:
class MyOpClass sh where
myOp :: Shape sh -> Int
shapeConstraint :: Either (sh :~: Circle') (sh :~: Square')
Now nobody can go adding any more instances (unless they use undefined, which would be impolite).
You could use typeclasses:
class MyOpClass sh where
myOp :: Shape sh -> Int
instance MyOpClass Circle' where
myOp (Circle r) = _
instance MyOpClass Square' where
myOP (Square s) = _
This doesn't feel like a particularly 'complete' solution to me - anyone could go back and add another instance MyOpClass Triangle' - but I can't think of any other solution. Potentially you could avoid this problem simply by not exporting the typeclass however.
Another solution I've noticed, though pretty verbose, is to create a kind that has a list of feature booleans. You can then pattern match on the features when restricting the type:
-- [circleOrSquare] [triangleOrSquare]
data Shape' =
Shape'' Bool
Bool
data Shape :: Shape' -> * where
Circle :: { radius :: Int} -> Shape (Shape'' True False)
Square :: { side :: Int} -> Shape (Shape'' True True)
Triangle
:: { a :: Int
, b :: Int
, c :: Int}
-> Shape (Shape'' False True)
test1 :: Shape (Shape'' True x) -> Int
test1 Circle {} = 2
test1 Square {} = 2
test1 Triangle {} = 2
Here, Triangle will fail to match:
• Couldn't match type ‘'True’ with ‘'False’
Inaccessible code in
a pattern with constructor:
Triangle :: Int -> Int -> Int -> Shape ('Shape'' 'False 'True),
in an equation for ‘test1’
• In the pattern: Triangle {}
In an equation for ‘test1’: test1 Triangle {} = 2
|
52 | test1 Triangle {} = 2
| ^^^^^^^^^^^
Unfortunately, I don't think you can write this as a record, which may be clearer and avoids the ordering of the features.
This might be usable in conjunction with the class examples for readability.

Haskell instance signatures

I'm a complete newbie in Haskell so please be patient.
Let's say I've got this class
class Indexable i where
at :: i a p -> p -> a
Now let's say I want to implement that typeclass for this data type:
data Test a p = Test [a]
What I tried is:
instance Indexable Test where
at (Test l) p = l `genericIndex` p
However it didn't compile, because p needs to be an Integral, however as far as I understand, it's impossibile to add the type signature to instances. I tried to use InstanceSigs, but failed.
Any ideas?
here is a version where you add the index-type to the class using MultiParamTypeClasses
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
module Index where
import Data.List (genericIndex)
class Indexable i f where
at :: forall a . f a -> i -> a
data Test a = Test [a]
instance Integral i => Indexable i Test where
at (Test as) i = as `genericIndex` i
here I need the FlexibleInstances because of the way the instance is declared and RankNTypes for the forall a . ;)
assuming this is your expected behavior:
λ> let test = Test [1..5]
λ> test `at` 3
4
λ> test `at` 0
1
λ> test `at` (0 :: Int)
1
λ> test `at` (1 :: Integer)
2
Just for fun, here's a very different solution which doesn't require any changes to your class declaration. (N.B. This answer is for fun only! I do not advocate keeping your class as-is; it seems a strange class definition to me.) The idea here is to push the burden of proof off from the class instance to the person constructing a value of type Test p a; we will demand that constructing such a value will require an Integral p instance in scope.
All this code stays exactly the same (but with a new extension turned on):
{-# LANGUAGE GADTs #-}
import Data.List
class Indexable i where
at :: i a p -> p -> a
instance Indexable Test where
at (Test l) p = l `genericIndex` p
But the declaration of your data type changes just slightly to demand an Integral p instance:
data Test a p where
Test :: Integral p => [a] -> Test a p
You are actually trying to do something fairly advanced. If I understand what you want, you actually need a multiparameter typeclass here, because your type parameter "p" depends on "i": for a list indexed by integer you need "p" to be integral, but for a table indexed by strings you need it to be "String", or at least an instance of "Ord".
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-} -- Enable the language extensions.
class Indexable i p | i -> p where
at :: i a -> p -> a
This says that the class is for two types, "i" and "p", and if you know "i" then "p" follows automatically. So if "i" is a list the "p" has to be Int, and if "i" is a "Map String a" then "p" has to be "String".
instance Indexable [a] Int where
at = (!!)
This declares the combination of [a] and Int as being an instance of Indexable.
user2407038 has provided an alternative approach using "type families", which is a more recent and sophisticated version of multiparameter type classes.
You can use associated type families and constraint kinds:
import GHC.Exts(Constraint)
class Indexable i where
type IndexableCtr i :: * -> Constraint
at :: IndexableCtr i p => i a p -> p -> a
instance Indexable Test where
type IndexableCtr Test = Integral
at (Test l) p = l `genericIndex` p
This defines the class Indexable with an associated type IndexableCtr which
is used to constraint the type of at.

Haskell Typeclass Instance based on canonical view

As a self assigned exercise of sorts, I'm playing around with implementing an algebra based numeric type heirarchy.
I'd like to specify that if a structure can be viewed in a canonical way as something that satisfies one of my typeclasses, then it should be an instance of that typeclass as well. To that end I've tried essentially the following:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
FlexibleContexts, FlexibleInstances #-}
class AbGp s a where
plus :: a -> a -> s -> a
zero :: s -> a
minus :: a -> a -> s -> a
class View a b c | a c -> b
view :: a -> b
instance (View s s1 a, AbGp s1 a) => AbGp s a
plus x y s = plus x y (view s)
zero = zero . view
minus x y s = minus x y (view s)
s should be thought of as holding the definitions of the operations in the group, and a as the type of the elements in the group.
But this doesn't work, which isn't surprising, but what I want to do now is:
Suppose I know that some type s, say s that represents a Ring, can be mapped canonically to s1 which is a datastructure I already have an instance for as an AbGp, then I would like s to also be automatically an instance of AbGp. How can I do this?
I'm thinking of doing the following, if it'll work, but I'd like to know if there is a better way:
instance (AbGp s1 a) => AbGp (s1,b) a where
-- ...

How can I use restricted constraints with GADTs?

I have the following code, and I would like this to fail type checking:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
import Control.Lens
data GADT e a where
One :: Greet e => String -> GADT e String
Two :: Increment e => Int -> GADT e Int
class Greet a where
_Greet :: Prism' a String
class Increment a where
_Increment :: Prism' a Int
instance Greet (Either String Int) where
_Greet = _Left
instance Increment (Either String Int) where
_Increment = _Right
run :: GADT e a -> Either String Int
run = go
where
go (One x) = review _Greet x
go (Two x) = review _Greet "Hello"
The idea is that each entry in the GADT has an associated error, which I'm modelling with a Prism into some larger structure. When I "interpret" this GADT, I provide a concrete type for e that has instances for all of these Prisms. However, for each individual case, I don't want to be able to use instances that weren't declared in the constructor's associated context.
The above code should be an error, because when I pattern match on Two I should learn that I can only use Increment e, but I'm using Greet. I can see why this works - Either String Int has an instance for Greet, so everything checks out.
I'm not sure what the best way to fix this is. Maybe I can use entailment from Data.Constraint, or perhaps there's a trick with higher rank types.
Any ideas?
The problem is you're fixing the final result type, so the instance exists and the type checker can find it.
Try something like:
run :: GADT e a -> e
Now the result type can't pick the instance for review and parametricity enforces your invariant.

Resources