Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion .github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ jobs:
cabal: ["3.2"]
ghc:
- "8.6.5"
# - "8.10.1"
- "8.10.1"

steps:
- uses: actions/checkout@v2
Expand Down
2 changes: 1 addition & 1 deletion circuit-notation.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ library
, clash-prelude >= 1.0
, containers
, data-default
, ghc >=8.6 && <8.8
, ghc (>=8.6 && <8.8) || (>=8.10 && < 9.0)
, syb
, lens
, mtl
Expand Down
18 changes: 15 additions & 3 deletions example/Example.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,13 +10,17 @@
This file contains examples of using the Circuit Notation.
-}

{-# LANGUAGE Arrows #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}

#if __GLASGOW_HASKELL__ < 810
{-# LANGUAGE Arrows #-}
#endif

{-# OPTIONS -fplugin=CircuitNotation #-}
{-# OPTIONS -fplugin-opt=CircuitNotation:debug #-}
{-# OPTIONS -Wall #-}
Expand All @@ -37,8 +41,16 @@ import Clash.Prelude (Signal, Vec(..))
idCircuit :: Circuit a a
idCircuit = idC

swapC :: Circuit (a,b) (b,a)
swapC = id $ circuit $ \ ~(a,b) -> ~(b,a)
#if __GLASGOW_HASKELL__ < 810
swapC0 :: Circuit (a,b) (b,a)
swapC0 = id $ circuit $ \ ~(a,b) -> ~(b,a)
#endif

swapC1 :: Circuit (a,b) (b,a)
swapC1 = id $ circuit $ \ ~(a,b) -> (b,a)

swapC2 :: Circuit (a,b) (b,a)
swapC2 = id $ circuit $ \ (a,b) -> (b,a)

circuitA :: Circuit () (DF domain Int)
circuitA = Circuit (\_ -> () :-> pure (DFM2S True 3))
Expand Down
17 changes: 13 additions & 4 deletions src/CircuitNotation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -114,6 +114,12 @@ isDollar = \case
HsVar _ (L _ v) -> v == GHC.mkVarUnqual "$"
_ -> False

-- | Is (-<)?
isFletching :: p ~ GhcPs => HsExpr p -> Bool
isFletching = \case
HsVar _ (L _ v) -> v == GHC.mkVarUnqual "-<"
_ -> False

imap :: (Int -> a -> b) -> [a] -> [b]
imap f = zipWith f [0 ..]

Expand Down Expand Up @@ -434,8 +440,10 @@ circuitBody = \case
L _ (HsArrApp _xapp (L _ (HsVar _ (L _ (GHC.Unqual occ)))) arg _ _)
| OccName.occNameString occ == "idC" -> circuitMasters .= bindMaster arg
#else
L _ (HsProc _ _ (L _ (HsCmdTop _ (L _ (HsCmdArrApp _xapp (L _ (HsVar _ (L _ (GHC.Unqual occ)))) arg _ _)))))
| OccName.occNameString occ == "idC" -> circuitMasters .= bindMaster arg
L _ (OpApp _ (L _ (HsVar _ (L _ (GHC.Unqual occ)))) (L _ op) port)
| isFletching op
, OccName.occNameString occ == "idC" -> do
circuitMasters .= bindMaster port
#endif

-- Otherwise create a binding and use that as the master. This is equivalent to changing
Expand Down Expand Up @@ -521,6 +529,7 @@ bindMaster (L loc expr) = case expr of
ExprWithTySig ty expr' -> PortType ty (bindMaster expr')
ELazyPat _ expr' -> Lazy loc (bindMaster expr')
#else
-- XXX: Untested?
HsProc _ _ (L _ (HsCmdTop _ (L _ (HsCmdArrApp _xapp (L _ (HsVar _ (L _ (GHC.Unqual occ)))) sig _ _))))
| OccName.occNameString occ == "Signal" -> SignalExpr sig
ExprWithTySig _ expr' ty -> PortType ty (bindMaster expr')
Expand All @@ -544,7 +553,7 @@ bodyBinding
-> GenLocated loc (HsExpr p)
-- ^ the statement with an optional @-<@
-> CircuitM ()
bodyBinding mInput lexpr@(L loc expr) =
bodyBinding mInput lexpr@(L loc expr) = do
case expr of
#if __GLASGOW_HASKELL__ < 810
HsArrApp _xhsArrApp circuit port HsFirstOrderApp True ->
Expand All @@ -554,7 +563,7 @@ bodyBinding mInput lexpr@(L loc expr) =
, bIn = fromMaybe (Tuple []) mInput
}]
#else
HsProc _ _ (L _ (HsCmdTop _ (L _ (HsCmdArrApp _xhsArrApp circuit port HsFirstOrderApp True)))) ->
OpApp _ circuit (L _ op) port | isFletching op -> do
circuitBinds <>= [Binding
{ bCircuit = circuit
, bOut = bindMaster port
Expand Down