Skip to content

Commit

Permalink
Show instances for TupR and LeftHandSide
Browse files Browse the repository at this point in the history
  • Loading branch information
tomsmeding committed Jun 13, 2023
1 parent dbc3b3b commit 450ed68
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 21 deletions.
16 changes: 10 additions & 6 deletions src/Data/Array/Accelerate/AST/LeftHandSide.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,11 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_HADDOCK hide #-}
-- |
-- Module : Data.Array.Accelerate.AST.LeftHandSide
Expand Down Expand Up @@ -40,6 +42,8 @@ data LeftHandSide s v env env' where
-> LeftHandSide s v2 env' env''
-> LeftHandSide s (v1, v2) env env''

deriving instance (forall a. Show (s a)) => Show (LeftHandSide s v env env')

pattern LeftHandSideUnit
:: () -- required
=> (env' ~ env, v ~ ()) -- provided
Expand Down
5 changes: 0 additions & 5 deletions src/Data/Array/Accelerate/Representation/Array.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,11 +74,6 @@ formatArrayR :: Format r (ArrayR a -> r)
formatArrayR = later $ \case
ArrayR shR eR -> bformat ("Array DIM" % int % " " % formatTypeR) (rank shR) eR

instance Show (TupR ArrayR e) where
show TupRunit = "()"
show (TupRsingle aR) = show aR
show (TupRpair aR1 aR2) = "(" ++ show aR1 ++ "," ++ show aR2 ++ ")"

formatArraysR :: Format r (TupR ArrayR e -> r)
formatArraysR = later $ \case
TupRunit -> "()"
Expand Down
19 changes: 9 additions & 10 deletions src/Data/Array/Accelerate/Representation/Type.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,11 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_HADDOCK hide #-}
-- |
-- Module : Data.Array.Accelerate.Representation.Type
Expand Down Expand Up @@ -43,10 +45,7 @@ data TupR s a where
TupRsingle :: s a -> TupR s a
TupRpair :: TupR s a -> TupR s b -> TupR s (a, b)

instance Show (TupR ScalarType a) where
show TupRunit = "()"
show (TupRsingle t) = show t
show (TupRpair a b) = "(" ++ show a ++ "," ++ show b ++ ")"
deriving instance (forall a. Show (s a)) => Show (TupR s t)

formatTypeR :: Format r (TypeR a -> r)
formatTypeR = later $ \case
Expand Down

0 comments on commit 450ed68

Please sign in to comment.