{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Clash.Core.TyCon
( TyCon (..)
, TyConName
, TyConOccName
, TyConMap
, AlgTyConRhs (..)
, mkKindTyCon
, isTupleTyConLike
, tyConDataCons
)
where
#ifndef MIN_VERSION_unbound_generics
#define MIN_VERSION_unbound_generics(x,y,z)(1)
#endif
import Control.DeepSeq
import Data.HashMap.Lazy (HashMap)
import GHC.Generics
import Unbound.Generics.LocallyNameless (Alpha(..))
import Unbound.Generics.LocallyNameless.Extra ()
#if MIN_VERSION_unbound_generics(0,3,0)
import Data.Monoid (All (..))
import Unbound.Generics.LocallyNameless (NthPatFind (..),
NamePatFind (..))
#endif
import Clash.Core.DataCon (DataCon)
import Clash.Core.Name
import {-# SOURCE #-} Clash.Core.Type (Kind, TyName, Type)
import Clash.Util
data TyCon
= AlgTyCon
{ tyConName :: !TyConName
, tyConKind :: !Kind
, tyConArity :: !Int
, algTcRhs :: !AlgTyConRhs
}
| FunTyCon
{ tyConName :: !TyConName
, tyConKind :: !Kind
, tyConArity :: !Int
, tyConSubst :: [([Type],Type)]
}
| PrimTyCon
{ tyConName :: !TyConName
, tyConKind :: !Kind
, tyConArity :: !Int
}
| SuperKindTyCon
{ tyConName :: !TyConName
}
deriving (Generic,NFData)
instance Show TyCon where
show (AlgTyCon {tyConName = n}) = "AlgTyCon: " ++ show n
show (FunTyCon {tyConName = n}) = "FunTyCon: " ++ show n
show (PrimTyCon {tyConName = n}) = "PrimTyCon: " ++ show n
show (SuperKindTyCon {tyConName = n}) = "SuperKindTyCon: " ++ show n
instance Eq TyCon where
(==) = (==) `on` tyConName
instance Ord TyCon where
compare = compare `on` tyConName
type TyConName = Name TyCon
type TyConOccName = OccName TyCon
type TyConMap = HashMap TyConOccName TyCon
data AlgTyConRhs
= DataTyCon
{ dataCons :: [DataCon]
}
| NewTyCon
{ dataCon :: !DataCon
, ntEtadRhs :: ([TyName],Type)
}
deriving (Show,Generic,NFData,Alpha)
instance Alpha TyCon where
aeq' c tc1 tc2 = aeq' c (tyConName tc1) (tyConName tc2)
fvAny' _ _ tc = pure tc
close _ _ tc = tc
open _ _ tc = tc
isPat _ = mempty
#if MIN_VERSION_unbound_generics(0,3,0)
isTerm _ = All True
nthPatFind _ = NthPatFind Left
namePatFind _ = NamePatFind (const (Left 0))
#else
isTerm _ = True
nthPatFind _ = Left
namePatFind _ _ = Left 0
#endif
swaps' _ _ tc = tc
lfreshen' _ tc cont = cont tc mempty
freshen' _ tc = return (tc,mempty)
acompare' c tc1 tc2 = acompare' c (tyConName tc1) (tyConName tc2)
mkKindTyCon :: TyConName
-> Kind
-> TyCon
mkKindTyCon name kind
= PrimTyCon name kind 0
isTupleTyConLike :: TyConName -> Bool
isTupleTyConLike nm = tupleName (name2String nm)
where
tupleName nm'
| '(' <- head nm'
, ')' <- last nm'
= all (== ',') (init $ tail nm')
tupleName _ = False
tyConDataCons :: TyCon -> [DataCon]
tyConDataCons (AlgTyCon {algTcRhs = DataTyCon { dataCons = cons}}) = cons
tyConDataCons (AlgTyCon {algTcRhs = NewTyCon { dataCon = con }}) = [con]
tyConDataCons _ = []