Skip to content
This repository has been archived by the owner on Jun 15, 2023. It is now read-only.

Commit

Permalink
Merge pull request #4 from kRITZCREEK/copy-from-target
Browse files Browse the repository at this point in the history
Adds a function to copy text from an existing element on the page
  • Loading branch information
beckyconning authored Jan 2, 2018
2 parents 86bc357 + 1b768af commit 21e83db
Show file tree
Hide file tree
Showing 4 changed files with 41 additions and 8 deletions.
6 changes: 6 additions & 0 deletions example/index.html
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,12 @@
<button class="test-selector" type="button" data-copy-text="From test-selector child#2!">
Copy
</button>
<div>
<input id="input-selector" type="text" value="Copy me!" />
<button id="input-button-selector" type="button">
Copy Text in Input
</button>
</div>
</form>
</body>
</html>
23 changes: 15 additions & 8 deletions example/src/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,22 +2,21 @@ module Main where

import Prelude

import CSS (Selector, fromString)
import Clipboard as C
import Control.Monad.Eff (Eff)

import Data.Maybe (fromMaybe)

import DOM (DOM)
import CSS (Selector, fromString)
import DOM.Event.EventTarget (addEventListener, eventListener)
import DOM.HTML (window)
import DOM.HTML.Event.EventTypes (load)
import DOM.HTML.Types (windowToEventTarget, htmlDocumentToDocument)
import DOM.HTML.Window (document)
import DOM.Node.NonElementParentNode (getElementById)
import DOM.Node.Types (Element, ElementId(..), documentToNonElementParentNode)
import DOM.Node.Element (getAttribute)

import Clipboard as C
import DOM.Node.NonElementParentNode (getElementById)
import DOM.Node.Types (Element, ElementId(ElementId), documentToNonElementParentNode)
import Data.Maybe (fromJust, fromMaybe)
import Data.Newtype (wrap)
import Partial.Unsafe (unsafePartial)

onLoad :: forall eff. (Eff (dom :: DOM | eff) Unit) -> Eff (dom :: DOM | eff) Unit
onLoad action
Expand All @@ -34,10 +33,18 @@ testElement el = void $ C.fromElement el $ stringFromAttr "data-copy-text" el
testSelector :: forall eff. Selector -> Eff (dom :: DOM | eff) Unit
testSelector sel = void $ C.fromCSSSelector sel $ stringFromAttr "data-copy-text"

testInputSelector :: forall eff. Eff (dom :: DOM | eff) Unit
testInputSelector = do
doc <- documentToNonElementParentNode <<< htmlDocumentToDocument <$> (document =<< window)
let getInput = unsafePartial fromJust <$> getElementById (wrap "input-selector") doc
button <- unsafePartial fromJust <$> getElementById (wrap "input-button-selector") doc
void $ C.fromElementWithTarget button getInput

main :: forall eff. Eff (dom :: DOM | eff) Unit
main = onLoad do
win <- window
doc <- documentToNonElementParentNode <<< htmlDocumentToDocument <$> document win
element <- getElementById (ElementId "test-element") doc
fromMaybe (pure unit) $ testElement <$> element
testSelector $ fromString ".test-selector"
testInputSelector
11 changes: 11 additions & 0 deletions src/Clipboard.js
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,17 @@ exports.fromStringSelector = makeFromX(function makeFromX$fromStringSelector (ef
};
});

exports.fromElementWithTarget = function (el) {
return function(targetSelector) {
return function() {
return new Clipboard(el, {
target: targetSelector
});
};
};
};


exports.destroy = function destroy (clipboard) {
return function destroy$Eff () {
clipboard.destroy();
Expand Down
9 changes: 9 additions & 0 deletions src/Clipboard.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Clipboard
( Clipboard
, fromElement
, fromCSSSelector
, fromElementWithTarget
, destroy
) where

Expand Down Expand Up @@ -33,6 +34,14 @@ foreign import fromStringSelector
-> (Element -> Eff (dom :: DOM | eff) String)
-> Eff (dom :: DOM | eff) Clipboard

-- | Registers a click handler on an Event, which triggers the passed `Eff` and
-- | copies the text inside the returned element to the clipboard.
foreign import fromElementWithTarget
:: forall eff
. Element
-> Eff (dom :: DOM | eff) Element
-> Eff (dom :: DOM | eff) Clipboard

foreign import destroy
:: forall eff
. Clipboard
Expand Down

0 comments on commit 21e83db

Please sign in to comment.