mirror of
https://github.com/Jaxan/ons-hs.git
synced 2025-04-27 22:57:44 +02:00
Adds trivial instances by using DerivingVia extension (needs new ghc)
This commit is contained in:
parent
db2b00273c
commit
7b2ee61978
4 changed files with 25 additions and 29 deletions
|
@ -1,22 +1,19 @@
|
||||||
|
{-# LANGUAGE DerivingVia #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
|
||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE StandaloneDeriving #-}
|
{-# LANGUAGE StandaloneDeriving #-}
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
|
||||||
module EquivariantSet where
|
module EquivariantSet where
|
||||||
|
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
|
|
||||||
import Data.Set (Set)
|
import Data.Set (Set)
|
||||||
import qualified Data.Set as Set
|
import qualified Data.Set as Set
|
||||||
import Prelude hiding (map, product)
|
import Prelude hiding (map, product)
|
||||||
|
|
||||||
import Orbit
|
import Orbit
|
||||||
import Support
|
|
||||||
|
|
||||||
|
|
||||||
-- Given a nominal type, we can construct equivariant sets. These simply use a
|
-- Given a nominal type, we can construct equivariant sets. These simply use a
|
||||||
|
@ -37,18 +34,8 @@ deriving instance Show (Orb a) => Show (EquivariantSet a)
|
||||||
deriving instance Ord (Orb a) => Monoid (EquivariantSet a)
|
deriving instance Ord (Orb a) => Monoid (EquivariantSet a)
|
||||||
deriving instance Ord (Orb a) => Semigroup (EquivariantSet a)
|
deriving instance Ord (Orb a) => Semigroup (EquivariantSet a)
|
||||||
|
|
||||||
-- We could derive a correct instance if I had written generic instances.
|
-- This action is trivial, since equivariant sets are equivariant
|
||||||
-- Didn't do that yet, but a direct instance is also nice.
|
deriving via (Trivial (EquivariantSet a)) instance Orbit (EquivariantSet a)
|
||||||
instance Orbit (EquivariantSet a) where
|
|
||||||
type Orb (EquivariantSet a) = EquivariantSet a
|
|
||||||
toOrbit = id
|
|
||||||
support _ = Support.empty
|
|
||||||
getElement x _ = x
|
|
||||||
index _ _ = 0
|
|
||||||
|
|
||||||
-- deriving instance Show (Orb a) => Show (Orb (EquivariantSet a))
|
|
||||||
-- deriving instance Eq (Orb a) => Eq (Orb (EquivariantSet a))
|
|
||||||
-- deriving instance Ord (Orb a) => Ord (Orb (EquivariantSet a))
|
|
||||||
|
|
||||||
|
|
||||||
-- Query
|
-- Query
|
||||||
|
|
12
src/Orbit.hs
12
src/Orbit.hs
|
@ -76,15 +76,3 @@ leftProduct pa pb oa ob = OrbPair (OrbRec oa) (OrbRec ob) <$> rincProdStrings (i
|
||||||
{-# INLINABLE separatedProduct #-}
|
{-# INLINABLE separatedProduct #-}
|
||||||
{-# INLINABLE leftProduct #-}
|
{-# INLINABLE leftProduct #-}
|
||||||
|
|
||||||
|
|
||||||
-- Data structure for the discrete nominal sets with a trivial action.
|
|
||||||
newtype Trivial a = Trivial { unTrivial :: a }
|
|
||||||
deriving (Eq, Ord, Show)
|
|
||||||
|
|
||||||
-- We need to remember the value!
|
|
||||||
instance Orbit (Trivial a) where
|
|
||||||
type Orb (Trivial a) = a
|
|
||||||
toOrbit (Trivial a) = a
|
|
||||||
support _ = Support.empty
|
|
||||||
getElement a _ = Trivial a
|
|
||||||
index _ _ = 0
|
|
||||||
|
|
|
@ -1,3 +1,4 @@
|
||||||
|
{-# LANGUAGE DerivingVia #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE DefaultSignatures #-}
|
{-# LANGUAGE DefaultSignatures #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
@ -57,6 +58,26 @@ class Orbit a where
|
||||||
{-# INLINABLE index #-}
|
{-# INLINABLE index #-}
|
||||||
|
|
||||||
|
|
||||||
|
-- Data structure for the discrete nominal sets with a trivial action.
|
||||||
|
newtype Trivial a = Trivial { unTrivial :: a }
|
||||||
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
|
-- For the trivial action, each element is its own orbit and is supported
|
||||||
|
-- by the empty set.
|
||||||
|
instance Orbit (Trivial a) where
|
||||||
|
type Orb (Trivial a) = a
|
||||||
|
toOrbit (Trivial a) = a
|
||||||
|
support _ = Support.empty
|
||||||
|
getElement a _ = Trivial a
|
||||||
|
index _ _ = 0
|
||||||
|
|
||||||
|
|
||||||
|
-- We can now define trivial instances for some basic types.
|
||||||
|
-- This uses a new Haskell extension (ghc 8.6.1)
|
||||||
|
deriving via (Trivial Bool) instance Orbit Bool
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
-- Generic class, so that custom data types can be derived
|
-- Generic class, so that custom data types can be derived
|
||||||
class GOrbit f where
|
class GOrbit f where
|
||||||
type GOrb f :: *
|
type GOrb f :: *
|
||||||
|
|
|
@ -15,7 +15,7 @@
|
||||||
# resolver:
|
# resolver:
|
||||||
# name: custom-snapshot
|
# name: custom-snapshot
|
||||||
# location: "./custom-snapshot.yaml"
|
# location: "./custom-snapshot.yaml"
|
||||||
resolver: lts-11.0
|
resolver: lts-13.1
|
||||||
|
|
||||||
# User packages to be built.
|
# User packages to be built.
|
||||||
# Various formats can be used as shown in the example below.
|
# Various formats can be used as shown in the example below.
|
||||||
|
|
Loading…
Add table
Reference in a new issue