Skip to content

Commit

Permalink
Naming convention fixes + Classes for tuples up to n=5
Browse files Browse the repository at this point in the history
- `Consumable`, `Dupable` and `Movable` uniformly implemented for tuples up to
n=5
- Fix some names/imports according to the project conventions
  • Loading branch information
tbagrel1 committed Mar 14, 2022
1 parent 29926db commit 941b83f
Show file tree
Hide file tree
Showing 5 changed files with 15 additions and 17 deletions.
2 changes: 1 addition & 1 deletion linear-base.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -125,7 +125,7 @@ library
containers,
ghc-prim,
hashable,
linear-generics >= 0.2 && < 0.3,
linear-generics >= 0.2,
storable-tuple,
text,
transformers,
Expand Down
13 changes: 6 additions & 7 deletions src/Control/Functor/Linear/Internal/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,6 @@
{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
Expand Down Expand Up @@ -43,12 +42,12 @@ module Control.Functor.Linear.Internal.Class
where

import qualified Control.Monad as NonLinear ()
import Data.Functor.Compose (Compose (..))
import Data.Functor.Identity (Identity (..))
import Data.Functor.Compose
import Data.Functor.Identity
import qualified Data.Functor.Linear.Internal.Applicative as Data
import qualified Data.Functor.Linear.Internal.Functor as Data
import qualified Data.Functor.Sum
import Data.Monoid.Linear
import Data.Functor.Sum
import Data.Monoid.Linear hiding (Sum)
import Data.Type.Bool
import Data.Unrestricted.Linear.Internal.Consumable
import GHC.TypeLits
Expand Down Expand Up @@ -242,9 +241,9 @@ instance Monoid a => Monad ((,) a) where
go b1 (b2, y) = (b1 <> b2, y)

deriving via
Generically1 (Data.Functor.Sum.Sum f g)
Generically1 (Sum f g)
instance
(Functor f, Functor g) => Functor (Data.Functor.Sum.Sum f g)
(Functor f, Functor g) => Functor (Sum f g)

deriving via
Generically1 (Compose f g)
Expand Down
5 changes: 0 additions & 5 deletions src/Data/Unrestricted/Linear/Internal/Consumable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -140,11 +140,6 @@ deriving via
instance
_ => Consumable (a, b, c, d, e)

deriving via
Generically (a, b, c, d, e, f)
instance
_ => Consumable (a, b, c, d, e, f)

deriving via
Generically (Prelude.Maybe a)
instance
Expand Down
6 changes: 3 additions & 3 deletions src/Data/Unrestricted/Linear/Internal/Dupable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@

module Data.Unrestricted.Linear.Internal.Dupable
( Dupable (..),
genericdupR,
genericDupR,
dup,
dup3,
dup4,
Expand Down Expand Up @@ -232,8 +232,8 @@ deriving newtype instance Dupable Semigroup.Any
instance (Generic a, GDupable (Rep a)) => Dupable (Generically a) where
dupR (Generically x) = lcoerce (Replicator.map (to :: Rep a x %1 -> a) (gdupR (from x)))

genericdupR :: (Generic a, GDupable (Rep a)) => a %1 -> Replicator a
genericdupR x = Replicator.map to (gdupR (from x))
genericDupR :: (Generic a, GDupable (Rep a)) => a %1 -> Replicator a
genericDupR x = Replicator.map to (gdupR (from x))

class GConsumable f => GDupable f where
gdupR :: f a %1 -> Replicator (f a)
Expand Down
6 changes: 5 additions & 1 deletion src/Data/Unrestricted/Linear/Internal/Movable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
Expand Down Expand Up @@ -118,6 +117,11 @@ deriving via
instance
(Movable a, Movable b, Movable c, Movable d) => Movable (a, b, c, d)

deriving via
Generically (a, b, c, d, e)
instance
(Movable a, Movable b, Movable c, Movable d, Movable e) => Movable (a, b, c, d, e)

instance Movable a => Movable (Prelude.Maybe a) where
move (Prelude.Nothing) = Ur Prelude.Nothing
move (Prelude.Just x) = Data.fmap Prelude.Just (move x)
Expand Down

0 comments on commit 941b83f

Please sign in to comment.