mirror of
https://github.com/Jaxan/nominal-lstar.git
synced 2025-04-27 22:57:45 +02:00
Adds ways to control strictness.
Increases efficiency by 1.5x (if used in observation table)
This commit is contained in:
parent
600f2fe1e8
commit
9ee755117e
3 changed files with 8 additions and 5 deletions
|
@ -22,6 +22,7 @@ executable NominalAngluin
|
||||||
build-depends:
|
build-depends:
|
||||||
base >=4.8 && <4.9,
|
base >=4.8 && <4.9,
|
||||||
containers,
|
containers,
|
||||||
|
deepseq,
|
||||||
haskeline,
|
haskeline,
|
||||||
mtl,
|
mtl,
|
||||||
NLambda
|
NLambda
|
||||||
|
|
|
@ -1,6 +1,7 @@
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
|
||||||
module Examples.Fifo (DataInput(..), fifoExample) where
|
module Examples.Fifo (DataInput(..), fifoExample) where
|
||||||
|
|
||||||
|
import Control.DeepSeq (NFData)
|
||||||
import GHC.Generics (Generic)
|
import GHC.Generics (Generic)
|
||||||
import NLambda
|
import NLambda
|
||||||
import Prelude (Eq, Int, Maybe (..), Ord, Show, length, reverse,
|
import Prelude (Eq, Int, Maybe (..), Ord, Show, length, reverse,
|
||||||
|
@ -34,7 +35,7 @@ sizeFifo (Fifo l1 l2) = length l1 + length l2
|
||||||
-- nominal automaton.
|
-- nominal automaton.
|
||||||
|
|
||||||
-- The alphabet:
|
-- The alphabet:
|
||||||
data DataInput = Put Atom | Get Atom deriving (Eq, Ord, Show, Generic)
|
data DataInput = Put Atom | Get Atom deriving (Eq, Ord, Show, Generic, NFData)
|
||||||
instance BareNominalType DataInput
|
instance BareNominalType DataInput
|
||||||
instance Contextual DataInput where
|
instance Contextual DataInput where
|
||||||
when f (Put a) = Put (when f a)
|
when f (Put a) = Put (when f a)
|
||||||
|
|
|
@ -1,4 +1,5 @@
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
{-# LANGUAGE DeriveAnyClass #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
|
@ -14,6 +15,8 @@ import GHC.Generics (Generic)
|
||||||
import Prelude (Bool (..), Eq, Ord, Show, ($), (++), (.), uncurry)
|
import Prelude (Bool (..), Eq, Ord, Show, ($), (++), (.), uncurry)
|
||||||
import qualified Prelude ()
|
import qualified Prelude ()
|
||||||
|
|
||||||
|
import Control.DeepSeq
|
||||||
|
|
||||||
-- An observation table is a function S x E -> O
|
-- An observation table is a function S x E -> O
|
||||||
-- (Also includes SA x E -> O)
|
-- (Also includes SA x E -> O)
|
||||||
type Table i o = Fun ([i], [i]) o
|
type Table i o = Fun ([i], [i]) o
|
||||||
|
@ -53,9 +56,7 @@ data State i = State
|
||||||
, ee :: Set [i] -- suffixes
|
, ee :: Set [i] -- suffixes
|
||||||
, aa :: Set i -- alphabet (remains constant)
|
, aa :: Set i -- alphabet (remains constant)
|
||||||
}
|
}
|
||||||
deriving (Show, Ord, Eq, Generic)
|
deriving (Show, Ord, Eq, Generic, NFData, BareNominalType)
|
||||||
|
|
||||||
instance NominalType i => BareNominalType (State i)
|
|
||||||
|
|
||||||
instance NominalType i => Conditional (State i) where
|
instance NominalType i => Conditional (State i) where
|
||||||
cond f s1 s2 = fromTup (cond f (toTup s1) (toTup s2)) where
|
cond f s1 s2 = fromTup (cond f (toTup s1) (toTup s2)) where
|
||||||
|
|
Loading…
Add table
Reference in a new issue