Code Monkey home page Code Monkey logo

uniplate's Introduction

Boilerplate Removal with Uniplate Hackage version Stackage versionBuild status

Generic transformations and queries are often referred to as boilerplate code - they remain relatively similar as the action performed by the code changes, and can often outnumber the actual intent of the code in terms of lines. While other generic traversal schemes have shown how powerful new features can be added to compilers, and how the type system can be manipulated into accepting these operations, the Uniplate library focuses on a conceptually simpler generic concept. A more complete document on Uniplate was published at the Haskell Workshop 2007, and is available from here, along with a video presentation, and the associated thesis chapter.

Uniplate is a simple, concise and fast generics library. To expand on that sentence:

  1. A generics library is one which allows you to write functions that operate over a data structure without tying down all aspects of the data structure. In particular, when writing an operation, you don't need to give a case for each constructor, and you don't have to state which fields are recursive.
  2. Uniplate is the simplest generics library. Using Uniplate is within the reach of all Haskell programmers.
  3. Uniplate is more concise than any other generics library.
  4. Uniplate is fast, not always the absolute fastest, but massively faster than many generics libraries.
  5. Uniplate is also less powerful than some other generics libraries, but if it does the job, you should use it.

The Uniplate library can be installed with the standard sequence of cabal commands:

cabal update
cabal install uniplate

This document proceeds as follows:

  1. Using Uniplate
  2. Using Biplate
  3. Making Uniplate Faster

Acknowledgements

Thanks to Björn Bringert for feedback on an earlier version of this document, Eric Mertens for various ideas and code snippets, and to Matt Naylor and Tom Shackell for helpful discussions.

Using Uniplate

To demonstrate the facilities of Uniplate, we use a simple arithmetic type:

{-# LANGUAGE DeriveDataTypeable #-}
module Expr where
import Data.Data
import Data.Generics.Uniplate.Data

data Expr = Val Int
          | Add Expr Expr
          | Sub Expr Expr
          | Div Expr Expr
          | Mul Expr Expr
          | Neg Expr
          deriving (Show, Eq, Data, Typeable)

In this definition, the Uniplate specific bits are bolded. The three extra parts are:

  • import Data.Generics.Uniplate.Data, this module contains all the Uniplate functions and definitions.
  • deriving (Data,Typeable), this deriving clause automatically adds the necessary instances for Uniplate.
  • {-# LANGUAGE DeriveDataTypeable #-}, this pragma turns on language support for the deriving line.

This definition makes use of the Scrap Your Boilerplate (SYB) based Uniplate implementation. The SYB implementation is compatible with the other implementations, but is slower (between 2 and 8 times) and requires some modest compiler extensions (implemented in GHC for many years). The alternative definition scheme is described towards the end of this document, in "Making Uniplate Faster". I recommend using the SYB implementation to start with, as it requires least work to use.

The Uniplate library defines two classes, Uniplate and Biplate, along with a number of functions. After importing Data.Generics.Uniplate.Data all types which have Datainstances automatically have the necessary Uniplate instances. In the following subsections we introduce the Uniplate functions, along with examples of using them. The two most commonly used functions are universe (used for queries) and transform (used for transformations).

Finding the constant values

universe :: Uniplate on => on -> [on]

When manipulating our little language it may be useful to know which constants have been used. This can be done with the following code:

constants :: Expr -> [Int]
constants x = nub [y | Val y <- universe x]

Here the only Uniplate method being used is universe, which when given a tree returns the root of the tree, and all its subtrees at all levels. This can be used to quickly flatten a tree structure into a list, for quick analysis via list comprehensions, as is done above.

Exercise: Write a function to test if an expression performs a division by the literal zero.

Basic optimisation

transform :: Uniplate on => (on -> on) -> on -> on

If we are negating a literal value, this computation can be performed in advance, so let's write a function to do this.

optimise :: Expr -> Expr
optimise = transform f
    where f (Neg (Val i)) = Val (negate i)
            f x = x

Here the Uniplate method being used is transform, which applies the given function to all the children of an expression, before applying it to the parent. This function can be thought of as bottom-up traversal of the data structure. The optimise code merely pattern matches on the negation of a literal, and replaces it with the literal.

Now let's add another optimisation into the same pass, just before the f x = x line insert:

f (Add x y) | x == y = Mul x (Val 2)

This takes an addition where two terms are equal and changes it into a multiplication, causing the nested expression to be executed only once.

Exercise: Extend the optimisation so that adding x to Mul x (Val 2) produces a multiplication by 3.

Depth of an expression

para :: Uniplate on => (on -> [res] -> res) -> on -> res

Now let's imagine that programmers in your language are paid by the depth of expression they produce, so let's write a function that computes the maximum depth of an expression.

depth :: Expr -> Int
depth = para (\_ cs -> 1 + maximum (0:cs))

This function performs a paramorphism (a bit like a fold) over the data structure. The function simply says that for each iteration, add one to the previous depth.

Exercise: Write a function that counts the maximum depth of addition only.

Renumbering literals

transformM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m on

The literal values need to be replaced with a sequence of numbers, each unique. This is unlikely for an arithmetic expression, but consider bound variables in lambda calculus and it starts to become a bit more plausible:

uniqueLits :: Expr -> Expr
uniqueLits x = evalState (transformM f x) [0..]
    where
        f (Val i) = do
            y:ys <- get
            put ys
            return (Val y)
        f x = return x

Here a monadic computation is required, the program needs to keep track of what the next item in the list to use is, and replace the current item. By using the state monad, this can be done easily.

Exercise: Allow each literal to occur only once, when a second occurrence is detected, replace that literal with zero.

Generating mutants

contexts :: Uniplate on => on -> [(on, on -> on)]

The person who is inputting the expression thinks they made a mistake, they suspect they got one of the values wrong by plus or minus one. Generate all the expressions they might have written.

mutate :: Expr -> [Expr]
mutate x = concat [[gen $ Val $ i-1, gen $ Val $ i+1]
                    | (Val i, gen) <- contexts x]

The transform function is useful for doing an operation to all nodes in a tree, but sometimes you only want to apply a transformation once. This is less common, but is sometimes required. The idea is that the context provides the information required to recreate the original expression, but with this node altered.

Exercise: Replace one multiplication with addition, if there are no multiplications return the original expression.

Fixed point optimisation

rewrite :: Uniplate on => (on -> Maybe on) -> on -> on

When slotting many transformations together, often one optimisation will enable another. For example, the the optimisation to reduce.

Descend

Do something different in the odd and even cases. Particularly useful if you have free variables and are passing state downwards.

Monadic Variants

descendM :: Monad m => (on -> m on) -> on -> m on                         -- descend
transformM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m on        -- transform
rewriteM :: (Monad m, Uniplate on) => (on -> m (Maybe on)) -> on -> m on  -- rewrite

All the transformations have both monadic and non-monadic versions.

Single Depth Varaints

children :: Uniplate on => on -> [on]           -- universe
descend :: (on -> on) -> on -> on               -- transform
holes :: Uniplate on => on -> [(on, on -> on)]  -- contexts

Lots of functions which operate over the entire tree also operate over just one level. Usually you want to use the multiple level version, but when needing more explicit control the others are handy.

Evaluation

If we need to evaluate an expression in our language, the answer is simple, don't use Uniplate! The reasons are that there is little boilerplate, you have to handle every case separately. For example in our language we can write:

eval :: Expr -> Int
eval (Val i) = i
eval (Add a b) = eval a + eval b
eval (Sub a b) = eval a - eval b
eval (Div a b) = eval a `div` eval b
eval (Mul a b) = eval a * eval b
eval (Neg a) = negate a

Using Biplate

All the operations defined in Uniplate have a corresponding Biplate instance. Typically the operations are just the same as Uniplate, with Bi on the end.

universeBi :: Biplate on with => on -> [with]
transformBi :: Biplate on with => (with -> with) -> on -> on
transformBiM :: (Monad m, Biplate on with) => (with -> m with) -> on -> m on

The biggest difference is for the functions childrenBi and descendBi. In these cases, if the starting type and the target type are the same, then the input value will be returned. For example:

childrenBi (Add (Val 1) (Val 2)) == [Add (Val 1) (Val 2)]
children (Add (Val 1) (Val 2)) == [Val 1, Val 2]

For example, you should never have descendBi in an inner recursive loop.

Making Uniplate Faster

To make Uniplate faster import Data.Generics.Uniplate.Direct and write your instances by hand.

Related work

uniplate's People

Contributors

chshersh avatar felixonmars avatar jacg avatar ndmitchell avatar np avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar

uniplate's Issues

Feature request: More transformations

e.g. a top-down version of transform, plus a "Maybe" variant.

All the above are transformations, so transform is rather vague. Maybe just suffix:

-- aka `transform`
transformUp  :: Uniplate on => (on -> on) -> (on -> on)
transformUp f = g where g = f . descend g
transformDown :: Uniplate on => (on -> on) -> (on -> on)
transformDown f = g where g = descend g . f
transformDownMay  :: Uniplate on => (on -> Maybe on) -> (on -> on)
transformDownMay f = g where g x = maybe x (descend g) $ f x

(And while we are refactoring, descend sounds like it does something recursively. Which got me confused for longer than i want to admit.)

Is it possible to get the `universeBi` in breadth-first-order?

Is it possible to use universeBi to get the output in breadth-first-order? It appears the results are returned in a depth-first fashion. I'm wondering how I can use uniplate to retrieve the universe in a breadth-first fashion. This isn't just idle curiosity, but rather I have a use case where the top-most provenance information stored in a tree of nodes is usually the best choice. I'd appreciate if you can give a pointer as to how I can achieve this.

To illustrate, consider the following toy program:

{-# LANGUAGE DeriveDataTypeable #-}

import Data.Data
import Data.Generics.Uniplate.Data

data A = A B Int deriving (Data, Typeable)
data B = B Int   deriving (Data, Typeable)

val :: A
val = A (B 1) 2

ints :: [Int]
ints = universeBi val

I get:

*Main> ints
[1,2]

But this is depth-first, as 1 is obtained from the B node. I'd rather get it in the breadth-first order, i.e., receive [2,1]. Is this achievable in uniplate?

Build fails with older GHCs

Building library for uniplate-1.6.13..
Data/Generics/Uniplate/Data.hs:3:16:
    unknown flag in  {-# OPTIONS_GHC #-} pragma: -Wno-orphans

Doesn't compile against ghc 901

Data/Generics/Uniplate/Internal/Utils.hs:26:17: error:
    Module ‘GHC.Exts’ does not export ‘SpecConstrAnnotation(..)’
   |
26 | import GHC.Exts(SpecConstrAnnotation(..))
   |                 ^^^^^^^^^^^^^^^^^^^^^^^^

Documentation problems

At least one correction:

  • The LANGUAGE pragma seems to be DeriveDataTypeable not DerivingDataTypeable.

The other problem is that I can't seem to get the first example to work:

{-# LANGUAGE DeriveDataTypeable #-}
module Expr where

import Data.Generics.Uniplate.Data

data Expr
    = Val Int
    | Add Expr Expr
    | Sub Expr Expr
    | Div Expr Expr
    | Mul Expr Expr
    | Neg Expr
    deriving (Show, Eq, Data, Typeable)

results in:

Not in scope: type constructor or class ‘Data’
Not in scope: type constructor or class ‘Typeable’

Tried GHC 7.6.3, 7.8.4 and 7.10.2. Clues?

Descend for more than two types

Hi Neil,

I haven't found a mailing list where I could ask a question about uniplate and hope it is ok, if I ask here.

Is there are possibility to do a descend which can map more than one type in the same pass? Something like

descend :: (on -> on) -> on -> on
descendBi :: (to -> to) -> from -> from
descendTri :: (a -> a) -> (b -> b) -> from -> from
...

These functions can be written by hand for a given data type, but I am just wondering if there is a generic solution for that.

Best,
Daniel

Uniplate with extensible functions

I'm curious if there's an easier/less-error-prone way to write traversals that go through a class method in Uniplate. Here's what I mean:

{-# LANGUAGE DeriveDataTypeable #-}

import Data.Data
import Data.List
import qualified Data.Generics.Uniplate.Data as G

data Name = Name String
       deriving (Data, Typeable, Eq)

data Expr = Var    Name
          | Lambda Name Expr
          | App    Expr Expr
          | Block  Stmt
       deriving (Data, Typeable)

data Stmt = StmtE Expr
           deriving (Data, Typeable)

instance Show Name where
  show (Name s) = s

instance Show Stmt where
  show (StmtE e) = '{' : show e ++ "}"

instance Show Expr where
  show (Var n)      = show n
  show (Lambda n e) = "\\" ++ show n ++ ". " ++ show e
  show (App e1 e2)  = '(' : show e1 ++ " " ++ show e2 ++ ")"
  show (Block s)    = show s

-- x (\y -> y)
x, y:: Name
x = Name "x"
y = Name "y"
e :: Expr
e = App (Block (StmtE (Var x))) (Lambda y (Var y))

test :: IO ()
test = do print e
          print $ freeVars e

---

class Data a => FreeVars a where
  freeVars :: a -> [Name]

instance FreeVars Name where
  freeVars n = [n]

instance FreeVars Stmt where
  freeVars s = nub $  concatMap freeVars (G.children   s :: [Stmt])
                   ++ concatMap freeVars (G.childrenBi s :: [Expr])

instance FreeVars Expr where
  freeVars (Var    n)   = [n]
  freeVars (Lambda n e) = filter (n /=) (freeVars e)
  freeVars e = let choice = 3
               in case choice of
                    1 -> nub $ G.universeBi e          -- [x, y]
                    2 -> G.para (\_ xs -> concat xs) e -- []
                    3 -> nub $  concatMap freeVars (G.children   e :: [Expr])
                             ++ concatMap freeVars (G.childrenBi e :: [Stmt])

Sorry, this is a wall of text; but all it really is doing is to compute free-variables in a lambda-calculus like language; pared down to demonstrate the issue.

It's the final case in freeVars for Expr that I'm concerned about. I'd really love to write it as in choice = 1, but that's wrong as it simply picks all the names. Option 2 would be nice, but it doesn't work since it only "folds" over expressions and hence misses statements. (You can run the expression test to see what I mean by changing the choice value.)

The only way I found how to write this correctly is choice = 3, i.e., extract "all" interesting subcomponents and collect the frees recursively. But this is very error prone, as I need to know that there are Stmt's inside Exprs, and if I add another kind of data, the code would break without any indication.

What's the best solution for this problem in Uniplate? I gather syb-with-class is really the way to go with this, but that doesn't really seem to be supported with GHC.Generics and I'm curious what the Uniplate solution for this sort of problem is.

Too slow using Uniplate.Data

From https://code.google.com/p/ndmitchell/issues/detail?id=27

I think I've figured out what is going on: this technique simply
doesn't work as well as we might hope it would! Here's why:

While you ignore the explicit parameter, in practice there's an
implicit dictionary parameter that is actually being used in res (Data/
Typeable). At first sight, that might sound okay -we want a caf per type
after all- but what happens is that we get a caf per dictionary
parameter
instead.

So, if several calls share the same dictionary parameter, they also get
the same caf, resulting in the memoization speedup we want (if the
substructure types are recomputed every time, that isn't going to be
faster than doing the travesals we want to
avoid). If, however, the calls are unrelated, they get separate
cafs, leading to recomputation of the substructure maps and
loss of performance.

Try this variation of the Paradise benchmark data:

genCom :: Company
genCom = C $ take 100000 $ cycle
[D "Research" laemmel [PU joost, PU marlow],
D "Strategy" blair []]

Then,

import Data.Generics.PlateData
uni_bill x = sum [ s | S s <- universeBi x]

turns out to be rather slower than expected, and a lot slower
than using a single top-level caf with a Map from TypeRefKeys
to IntSets of TypeRefKeys (listing for each type of interest its
substructure types).

Am I on the right track here?
Claus


I think I've figured out what is going on: this technique simply
doesn't work as well as we might hope it would! Here's why:

While you ignore the explicit parameter, in practice there's an
implicit dictionary parameter that is actually being used in res
(Data/Typeable). At first sight, that might sound okay -we want a caf per
type after all- but what happens is that we get a caf per dictionary
parameter
instead.

My tests show that is wrong. Inserting a trace around the type map
creation shows it is only called twice, with Company/Salary and
Salary/Salary. Profiling shows much the same result.

Try this variation of the Paradise benchmark data:

genCom :: Company
genCom = C $ take 100000 $ cycle
[D "Research" laemmel [PU joost, PU marlow],
D "Strategy" blair []]

I did, and Uniplate underperforms. I'm not entirely sure why this is
yet, but my thoughts are kind of drifting towards a space leak, but I
do need to track it down. It seems as you increase the size of the
expressions the PlateData technique performs worse at queries.

Am I on the right track here?

My guess is no - I think in Uniplate the CAF inside an instance trick
works. But you have certainly found something ...

Thanks

Neil
Aug 20, 2008 Delete comment Project Member #1 ndmitchell
(No comment was entered for this change.)
Labels: -Project-Uniplate Proj-Uniplate
Jan 3, 2010 Delete comment Project Member #2 ndmitchell
I do now use the top-level CAF trick, so this problem might be alleviated - but there
is still a bug somewhere in it.
Jan 10, 2010 Delete comment Project Member #3 ndmitchell
I added a slowdown mode:

Running with Uniplate.Data:
Testing for slowdown caused by bug #27
Running with n=1 takes 0.75s, ratio 0.75
Running with n=2 takes 2.66s, ratio 1.33
Running with n=3 takes 5.86s, ratio 1.95
Running with n=4 takes 10.23s, ratio 2.56
Running with n=5 takes 15.97s, ratio 3.19
Running with n=6 takes 22.86s, ratio 3.81

Running with Uniplate.Direct (at 10x the list size):
Testing for slowdown caused by bug #27
Running with n=1 takes 0.44s, ratio 0.44
Running with n=2 takes 1.29s, ratio 0.64
Running with n=3 takes 2.23s, ratio 0.74
Running with n=4 takes 3.11s, ratio 0.78

So some slight slowdown is to be expected (probably much more GC going on, and larger
heaps) - but the level shown by Uniplate.Data suggests a bug somewhere.
Summary: Too slow using Uniplate.Data
Jan 10, 2010 Delete comment Project Member #4 ndmitchell
Running with SYB alone gives:
Testing for slowdown caused by bug #27
Running with n=1 takes 1.05s, ratio 1.05
Running with n=2 takes 2.69s, ratio 1.35
Running with n=3 takes 5.29s, ratio 1.76
Running with n=4 takes 8.72s, ratio 2.18
Running with n=5 takes 13.11s, ratio 2.62
Running with n=6 takes 17.83s, ratio 2.97
Running with n=7 takes 23.46s, ratio 3.35

So it's possible increased memory pressure makes it perform worse, so this is really
a GHC "bug".

Uniplate.Data with nested datatype doesn't terminate

From https://code.google.com/p/ndmitchell/issues/detail?id=490

What steps will reproduce the problem?

  1. Load the attached file into ghci or compile it with ghc.
  2. Evaluate (e.g. by printing) test1 or test2

What is the expected output? What do you see instead?

Immediate evaluation and:

test1: [1]
test2: [2,3,5,7,11,13,17,19]

What version of the product are you using? On what operating system?
(Saying "latest" is fine, especially for Hoogle web search)

Latest.

Please provide any additional information below.

If you abort the operation early, you see the value. If you don't, then your memory is consumed by an exploding computation.

{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}

module PerfectDatatype where

import Data.Generics
import Data.Generics.Uniplate.Data

data Perfect a = Zero a | Succ (Perfect (Fork a)) deriving (Show, Data)
data Fork a = Fork a a deriving (Show, Data)

deriving instance Typeable1 Perfect
deriving instance Typeable1 Fork

selectIntPerfect :: Perfect Int -> [Int]
selectIntPerfect = universeBi

ex1 :: Perfect Int
ex1 = Zero 1

ex2 :: Perfect Int
ex2 = Succ (Succ (Succ (Zero (Fork (Fork (Fork 2 3)
                                         (Fork 5 7))
                                   (Fork (Fork 11 13)
                                         (Fork 17 19))))))

test1 :: [Int]
test1 = selectIntPerfect ex1

test2 :: [Int]
test2 = selectIntPerfect ex2

No instance Biplate [a] a?

Hi, I'm curious why there's no Biplate [a] a instance defined in the library, just a Biplate [Char] Char one.

Thanks!

Applicative Uniplate

Hello!

As it happens, I'm writing some code to do concurrent fetching of resources as a Traversal, and this involves an applicative promise-like thing. It would be very convenient to then be able to perform this applicative traversal at certain leafs in a big data structure. This is possible with lens, but (I think) not with the currently released Uniplate—but we avoid lens, and already use lots of Uniplate!

Coincidentally I saw that @ndmitchell was working on applicativizing Uniplate only recently, so actually this is less of an "issue" and more of a curious inquiry into the status, whether this will be released, etc. :)

The code is already mostly done anyway, but with some ugly manual descent/replace, and it would be be fun to get rid of this!

Working with Biplate and Vector does not behave in a similar way as list

Hey, thanks for this lovely package.

I tried using uniplate with vector but got an unexpected behaviour. It seems that transformBi does not apply a function over vectors the same way it would work over a list:

stack ghci --package uniplate --package vector
Configuring GHCi with the following packages: 
GHCi, version 8.2.2: http://www.haskell.org/ghc/  :? for help
Loaded GHCi configuration from /home/gilm/.ghci
Loaded GHCi configuration from /tmp/haskell-stack-ghci/2a3bbd58/ghci-script
λ> import Data.Generics.Uniplate.Data
λ> import qualified Data.Vector as V
λ> transformBi not [False]
[True]
λ> transformBi not (V.singleton False)
[False]

Any ideas to what's going on?

Thanks!

Mapping elements of a zipper without loosing focus

Hi,

I need a function that maps a function over all elements that a zipper contains without loosing the zippers focus:

mapZipper :: Uniplate a => (a -> a) -> Zipper a a -> Zipper a a

My current solution is a bit ugly. I wrote a wrapper type that contains the current position of the zipper as a list of Down | Left | Right and the vanilla uniplate library zipper:

mapZipper :: Uniplate a => (a -> a) -> Zipper a a -> Zipper a a
mapZipper f (Zipper directions z) = fromJust
                                  $ moveBack directions
                                  $ zipper
                                  $ transform f
                                  $ fromZipper z
    where
        moveBack (Down:dirs)  = moveBack dirs <=< down
        moveBack (Left:dirs)  = moveBack dirs <=< left
        moveBack (Right:dirs) = moveBack dirs <=< right
        moveBack []      = return

Is there a better way to do this, maybe without even moving to the top of the zipper?

Best,

Sven

Optimise the Direct method

From https://code.google.com/p/ndmitchell/issues/detail?id=536

I should optimise the Direct code, particularly for descend. I think if I defined it as:

descend f = descendBiplate f biplate

Then introduced rules:

descendBiplate f (a |+ b) = descendBiplate f a |- descend f b

descendBiplate f (a |* b) = descendBiplate f a |- f b

Plus a few rules to move the |- to the left, it might give significant optimisations. Should really put in some decent benchmarking before doing this, see Bug #353 .

Support hashable-1.3.0.0

There is a new major release of hashable. As far as I can see, bumping the upper bound is enough to support it.

Interestingly, this is actually causing problems at the moment (cabal-install is having a hard time finding installation plans, e.g. lambdabot/lambdabot#183).

Check strict Int fields still work

Lennart reports that making the Int fields in SrcSpanInfo and SrcSpan in haskell-src-exts stops Uniplate using the fast data traversal mechanisms. I should confirm it works as designed, and add a test to ensure it never breaks in future.

Uniplate.Direct requires derive Data ??

Maybe i misunderstood that Uniplate.Direct doesn't require deriving Data and Typeable? When i try to use Uniplate.Direct i get this error

import Data.Generics.Uniplate.Direct (plate, (|-))

aeis :: Data from => from -> from
aeis = transformBi x
  where x (IExtended a) = let updated_text :: Text
                              updated_text = T.concat ["\\", snd $ t_text a, "\\"]
                          in IExtended $ a {t_text = (fst $ t_text a, updated_text)}
        x a = a
{-
    • Could not deduce (Data Identifier)
        arising from a use of ‘transformBi’
      from the context: Data from
        bound by the type signature for:
                   aeis :: Data from => from -> from
        at /home/flip111/haskell/vhdl/src/Main.hs:87:1-33
    • In the expression: transformBi x
      In an equation for ‘aeis’:
          aeis
            = transformBi x
            where
                x (IExtended a) = let ... in IExtended $ a {t_text = ...}
                x a = a
-}

-- https://hackage.haskell.org/package/uniplate-1.6.12/docs/Data-Generics-Uniplate-Direct.html

data Identifier = IBasic BasicIdentifier | IExtended ExtendedIdentifier deriving (Eq, Show, Generic)
instance Uniplate Identifier where
  uniplate (IBasic    x) = plate IBasic    |- x
  uniplate (IExtended x) = plate IExtended |- x

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.