{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, NoMonomorphismRestriction, FlexibleContexts, FunctionalDependencies, ScopedTypeVariables #-} {- Data a typed dataflow language This is a Haskell-embedded DSL representing numeric operations (DSP code). It resembles SSA/ANF minus control flow operations. This language is parameterized by a Monad to allow capturing of structural elements (i.e. sharing structure). However, the idea is that its semantics is pure. See the `Value' instance below. -} module Data(Repr(..), Data(..), DataField(..), DataRing(..), Tint, Tfloat, Tbool, Tvoid, DataWord(..) ) where import StateCont import Control.Monad import Control.Monad.Identity import Prelude hiding (div) import Struct import Type {- Primitive data types -} type Tfloat = Double type Tint = Int type Tbool = Bool type Tvoid = () class DataWord t where primType :: t -> Type instance DataWord Tbool where primType _ = Type ABool 0 instance DataWord Tint where primType _ = Type AInt 0 instance DataWord Tfloat where primType _ = Type AFloat 0 instance DataWord Tvoid where primType _ = Type AVoid 0 {- Pointers / Arrays are represented as (Tint ->) wrappers. -} instance DataWord t => DataWord (Tint -> t) where primType _ = Type base (1 + order) where Type base order = primType (undefined :: t) {- There are 2 ways in which data structures are used. One is in argument passing, which never leaks through to the Term language representation. The other is in data storage, where we need the low-level language's primitive data types to support tupling. Structs are also words. This is to support C structs and maybe later unions. These can behave as a real atomic type (a single variable), but support destructuring. -} instance (DataWord t1, DataWord t2) => DataWord (t1,t2) where primType _ = Type (ATree $ ACons ts1 ts2) 0 where ts1 = primType (undefined :: t1) ts2 = primType (undefined :: t2) instance DataWord t => DataWord (L t) where -- This instance terminates the recursion on (,) primType _ = Type (ATree $ AAtom $ primType (undefined :: t)) 0 instance DataWord (L ()) where -- Empty fillers for () type. primType _ = Type (ATree ANil) 0 {- Sets of arithmetic ops are defined per primitive data type t. -} class (Repr r, Monad m) => DataRing m r t | r -> m where add :: r t -> r t -> m (r t) sub :: r t -> r t -> m (r t) mul :: r t -> r t -> m (r t) eq :: r t -> r t -> m (r Tbool) lt :: r t -> r t -> m (r Tbool) lit :: t -> m (r t) class DataRing m r t => DataField m r t | r -> m, m -> r where div :: r t -> r t -> m (r t) -- This I hope makes things a bit more easy to manage.. class Repr r class (Repr r, Monad m ,DataRing m r Tint ,DataField m r Tfloat) => Data m r | r -> m, m -> r where true :: m (r Tbool) false :: m (r Tbool) i2f :: r Tint -> m (r Tfloat) f2i :: r Tfloat -> m (r Tint) -- Primitive structure (un)packing. unpack :: (DataWord s, StructVar sr, Struct r s sr) => r s -> m sr pack :: (DataWord s, Struct r s sr) => sr -> m (r s) {- INSTANCES -} {- 1. Value: see Value.hs -} {- 2. Code: see Code.hs -}